diff options
Diffstat (limited to 'bittorrent/src')
26 files changed, 7685 insertions, 0 deletions
diff --git a/bittorrent/src/Network/BitTorrent.hs b/bittorrent/src/Network/BitTorrent.hs new file mode 100644 index 00000000..91a58887 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent.hs | |||
@@ -0,0 +1,61 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | {-# LANGUAGE RecordWildCards #-} | ||
9 | module Network.BitTorrent | ||
10 | ( -- * Client | ||
11 | Options (..) | ||
12 | |||
13 | -- ** Session | ||
14 | , Client | ||
15 | , clientPeerId | ||
16 | , clientListenerPort | ||
17 | , allowedExtensions | ||
18 | |||
19 | -- ** Initialization | ||
20 | , LogFun | ||
21 | , newClient | ||
22 | , closeClient | ||
23 | , withClient | ||
24 | |||
25 | -- ** Monadic | ||
26 | , MonadBitTorrent (..) | ||
27 | , BitTorrent | ||
28 | , runBitTorrent | ||
29 | , getClient | ||
30 | , simpleClient | ||
31 | |||
32 | -- * Torrent | ||
33 | -- ** Source | ||
34 | , InfoHash | ||
35 | , Magnet | ||
36 | , InfoDict | ||
37 | , Torrent | ||
38 | |||
39 | -- ** Handle | ||
40 | , Handle | ||
41 | , handleTopic | ||
42 | , handleTrackers | ||
43 | , handleExchange | ||
44 | |||
45 | , TorrentSource(openHandle) | ||
46 | , closeHandle | ||
47 | , getHandle | ||
48 | , getIndex | ||
49 | |||
50 | -- ** Control | ||
51 | , start | ||
52 | , pause | ||
53 | , stop | ||
54 | |||
55 | -- * Events | ||
56 | , EventSource (..) | ||
57 | ) where | ||
58 | |||
59 | import Data.Torrent | ||
60 | import Network.BitTorrent.Client | ||
61 | import Network.BitTorrent.Internal.Types \ No newline at end of file | ||
diff --git a/bittorrent/src/Network/BitTorrent/Client.hs b/bittorrent/src/Network/BitTorrent/Client.hs new file mode 100644 index 00000000..c84290dd --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Client.hs | |||
@@ -0,0 +1,195 @@ | |||
1 | {-# LANGUAGE FlexibleInstances #-} | ||
2 | {-# LANGUAGE TypeSynonymInstances #-} | ||
3 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
4 | {-# LANGUAGE TemplateHaskell #-} | ||
5 | module Network.BitTorrent.Client | ||
6 | ( -- * Options | ||
7 | Options (..) | ||
8 | |||
9 | -- * Client session | ||
10 | , Client | ||
11 | |||
12 | -- ** Session data | ||
13 | , clientPeerId | ||
14 | , clientListenerPort | ||
15 | , allowedExtensions | ||
16 | |||
17 | -- ** Session initialization | ||
18 | , LogFun | ||
19 | , newClient | ||
20 | , closeClient | ||
21 | , withClient | ||
22 | , simpleClient | ||
23 | |||
24 | -- * BitTorrent monad | ||
25 | , MonadBitTorrent (..) | ||
26 | , BitTorrent | ||
27 | , runBitTorrent | ||
28 | , getClient | ||
29 | |||
30 | -- * Handle | ||
31 | , Handle | ||
32 | , handleTopic | ||
33 | , handleTrackers | ||
34 | , handleExchange | ||
35 | |||
36 | -- ** Construction | ||
37 | , TorrentSource (..) | ||
38 | , closeHandle | ||
39 | |||
40 | -- ** Query | ||
41 | , getHandle | ||
42 | , getIndex | ||
43 | |||
44 | -- ** Management | ||
45 | , start | ||
46 | , pause | ||
47 | , stop | ||
48 | ) where | ||
49 | |||
50 | import Control.Applicative | ||
51 | import Control.Exception | ||
52 | import Control.Concurrent | ||
53 | import Control.Concurrent.Chan.Split as CS | ||
54 | import Control.Monad.Logger | ||
55 | import Control.Monad.Trans | ||
56 | import Control.Monad.Trans.Resource | ||
57 | |||
58 | import Data.Default | ||
59 | import Data.HashMap.Strict as HM | ||
60 | import Data.Text | ||
61 | import Network | ||
62 | |||
63 | import Data.Torrent | ||
64 | import Network.Address | ||
65 | import Network.BitTorrent.Client.Types | ||
66 | import Network.BitTorrent.Client.Handle | ||
67 | import Network.BitTorrent.DHT as DHT hiding (Options) | ||
68 | import Network.BitTorrent.Tracker as Tracker hiding (Options) | ||
69 | import Network.BitTorrent.Exchange as Exchange hiding (Options) | ||
70 | import qualified Network.BitTorrent.Exchange as Exchange (Options(..)) | ||
71 | |||
72 | |||
73 | data Options = Options | ||
74 | { optFingerprint :: Fingerprint | ||
75 | , optName :: Text | ||
76 | , optPort :: PortNumber | ||
77 | , optExtensions :: [Extension] | ||
78 | , optNodeAddr :: NodeAddr IPv4 | ||
79 | , optBootNode :: Maybe (NodeAddr IPv4) | ||
80 | } | ||
81 | |||
82 | instance Default Options where | ||
83 | def = Options | ||
84 | { optFingerprint = def | ||
85 | , optName = "hs-bittorrent" | ||
86 | , optPort = 6882 | ||
87 | , optExtensions = [] | ||
88 | , optNodeAddr = "0.0.0.0:6882" | ||
89 | , optBootNode = Nothing | ||
90 | } | ||
91 | |||
92 | exchangeOptions :: PeerId -> Options -> Exchange.Options | ||
93 | exchangeOptions pid Options {..} = Exchange.Options | ||
94 | { optPeerAddr = PeerAddr (Just pid) (peerHost def) optPort | ||
95 | , optBacklog = optBacklog def | ||
96 | } | ||
97 | |||
98 | connHandler :: MVar (HashMap InfoHash Handle) -> Exchange.Handler | ||
99 | connHandler tmap ih = do | ||
100 | m <- readMVar tmap | ||
101 | case HM.lookup ih m of | ||
102 | Nothing -> error "torrent not found" | ||
103 | Just (Handle {..}) -> return handleExchange | ||
104 | |||
105 | initClient :: Options -> LogFun -> ResIO Client | ||
106 | initClient opts @ Options {..} logFun = do | ||
107 | pid <- liftIO genPeerId | ||
108 | tmap <- liftIO $ newMVar HM.empty | ||
109 | |||
110 | let peerInfo = PeerInfo pid Nothing optPort | ||
111 | let mkTracker = Tracker.newManager def peerInfo | ||
112 | (_, tmgr) <- allocate mkTracker Tracker.closeManager | ||
113 | |||
114 | let mkEx = Exchange.newManager (exchangeOptions pid opts) (connHandler tmap) | ||
115 | (_, emgr) <- allocate mkEx Exchange.closeManager | ||
116 | |||
117 | let mkNode = DHT.newNode defaultHandlers def optNodeAddr logFun Nothing | ||
118 | (_, node) <- allocate mkNode DHT.closeNode | ||
119 | |||
120 | resourceMap <- getInternalState | ||
121 | eventStream <- liftIO newSendPort | ||
122 | |||
123 | return Client | ||
124 | { clientPeerId = pid | ||
125 | , clientListenerPort = optPort | ||
126 | , allowedExtensions = toCaps optExtensions | ||
127 | , clientResources = resourceMap | ||
128 | , trackerManager = tmgr | ||
129 | , exchangeManager = emgr | ||
130 | , clientNode = node | ||
131 | , clientTorrents = tmap | ||
132 | , clientLogger = logFun | ||
133 | , clientEvents = eventStream | ||
134 | } | ||
135 | |||
136 | newClient :: Options -> LogFun -> IO Client | ||
137 | newClient opts logFun = do | ||
138 | s <- createInternalState | ||
139 | runInternalState (initClient opts logFun) s | ||
140 | `onException` closeInternalState s | ||
141 | |||
142 | closeClient :: Client -> IO () | ||
143 | closeClient Client {..} = closeInternalState clientResources | ||
144 | |||
145 | withClient :: Options -> LogFun -> (Client -> IO a) -> IO a | ||
146 | withClient opts lf action = bracket (newClient opts lf) closeClient action | ||
147 | |||
148 | -- do not perform IO in 'initClient', do it in the 'boot' | ||
149 | --boot :: BitTorrent () | ||
150 | --boot = do | ||
151 | -- Options {..} <- asks options | ||
152 | -- liftDHT $ bootstrap (maybeToList optBootNode) | ||
153 | |||
154 | -- | Run bittorrent client with default options and log to @stderr@. | ||
155 | -- | ||
156 | -- For testing purposes only. | ||
157 | -- | ||
158 | simpleClient :: BitTorrent () -> IO () | ||
159 | simpleClient m = do | ||
160 | runStderrLoggingT $ LoggingT $ \ logger -> do | ||
161 | withClient def logger (`runBitTorrent` m) | ||
162 | |||
163 | {----------------------------------------------------------------------- | ||
164 | -- Torrent identifiers | ||
165 | -----------------------------------------------------------------------} | ||
166 | |||
167 | class TorrentSource s where | ||
168 | openHandle :: FilePath -> s -> BitTorrent Handle | ||
169 | |||
170 | instance TorrentSource InfoHash where | ||
171 | openHandle path ih = openMagnet path (nullMagnet ih) | ||
172 | {-# INLINE openHandle #-} | ||
173 | |||
174 | instance TorrentSource Magnet where | ||
175 | openHandle = openMagnet | ||
176 | {-# INLINE openHandle #-} | ||
177 | |||
178 | instance TorrentSource InfoDict where | ||
179 | openHandle path dict = openTorrent path (nullTorrent dict) | ||
180 | {-# INLINE openHandle #-} | ||
181 | |||
182 | instance TorrentSource Torrent where | ||
183 | openHandle = openTorrent | ||
184 | {-# INLINE openHandle #-} | ||
185 | |||
186 | instance TorrentSource FilePath where | ||
187 | openHandle contentDir torrentPath = do | ||
188 | t <- liftIO $ fromFile torrentPath | ||
189 | openTorrent contentDir t | ||
190 | {-# INLINE openHandle #-} | ||
191 | |||
192 | getIndex :: BitTorrent [Handle] | ||
193 | getIndex = do | ||
194 | Client {..} <- getClient | ||
195 | elems <$> liftIO (readMVar clientTorrents) | ||
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 @@ | |||
1 | module 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 | |||
20 | import Control.Concurrent.Chan.Split | ||
21 | import Control.Concurrent.Lifted as L | ||
22 | import Control.Monad | ||
23 | import Control.Monad.Trans | ||
24 | import Data.Default | ||
25 | import Data.List as L | ||
26 | import Data.HashMap.Strict as HM | ||
27 | |||
28 | import Data.Torrent | ||
29 | import Network.BitTorrent.Client.Types as Types | ||
30 | import Network.BitTorrent.DHT as DHT | ||
31 | import Network.BitTorrent.Exchange as Exchange | ||
32 | import Network.BitTorrent.Tracker as Tracker | ||
33 | |||
34 | {----------------------------------------------------------------------- | ||
35 | -- Safe handle set manupulation | ||
36 | -----------------------------------------------------------------------} | ||
37 | |||
38 | allocHandle :: InfoHash -> BitTorrent Handle -> BitTorrent Handle | ||
39 | allocHandle 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 | |||
54 | freeHandle :: InfoHash -> BitTorrent () -> BitTorrent () | ||
55 | freeHandle 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 | |||
65 | lookupHandle :: InfoHash -> BitTorrent (Maybe Handle) | ||
66 | lookupHandle ih = do | ||
67 | Client {..} <- getClient | ||
68 | handles <- readMVar clientTorrents | ||
69 | return (HM.lookup ih handles) | ||
70 | |||
71 | {----------------------------------------------------------------------- | ||
72 | -- Initialization | ||
73 | -----------------------------------------------------------------------} | ||
74 | |||
75 | newExchangeSession :: FilePath -> Either InfoHash InfoDict -> BitTorrent Exchange.Session | ||
76 | newExchangeSession 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. | ||
82 | openTorrent :: FilePath -> Torrent -> BitTorrent Handle | ||
83 | openTorrent 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'. | ||
100 | openMagnet :: FilePath -> Magnet -> BitTorrent Handle | ||
101 | openMagnet 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. | ||
120 | closeHandle :: Handle -> BitTorrent () | ||
121 | closeHandle 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 | |||
132 | modifyStatus :: HandleStatus -> Handle -> (HandleStatus -> BitTorrent ()) -> BitTorrent () | ||
133 | modifyStatus 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. | ||
144 | start :: Handle -> BitTorrent () | ||
145 | start 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. | ||
161 | pause :: Handle -> BitTorrent () | ||
162 | pause _ = return () | ||
163 | |||
164 | -- | Stop downloading, uploading and announcing this torrent. | ||
165 | stop :: Handle -> BitTorrent () | ||
166 | stop 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 | |||
180 | getHandle :: InfoHash -> BitTorrent Handle | ||
181 | getHandle ih = do | ||
182 | mhandle <- lookupHandle ih | ||
183 | case mhandle of | ||
184 | Nothing -> error "should we throw some exception?" | ||
185 | Just h -> return h | ||
186 | |||
187 | getStatus :: Handle -> IO HandleStatus | ||
188 | getStatus 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 #-} | ||
6 | module 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 | |||
24 | import Control.Applicative | ||
25 | import Control.Concurrent | ||
26 | import Control.Concurrent.Chan.Split as CS | ||
27 | import Control.Monad.Base | ||
28 | import Control.Monad.Logger | ||
29 | import Control.Monad.Reader | ||
30 | import Control.Monad.Trans.Control | ||
31 | import Control.Monad.Trans.Resource | ||
32 | import Data.Function | ||
33 | import Data.HashMap.Strict as HM | ||
34 | import Data.Ord | ||
35 | import Network | ||
36 | import System.Log.FastLogger | ||
37 | |||
38 | import Data.Torrent | ||
39 | import Network.Address | ||
40 | import Network.BitTorrent.Internal.Types as Types | ||
41 | import Network.BitTorrent.DHT as DHT | ||
42 | import Network.BitTorrent.Exchange as Exchange | ||
43 | import Network.BitTorrent.Tracker as Tracker hiding (Event) | ||
44 | |||
45 | data HandleStatus | ||
46 | = Running | ||
47 | | Stopped | ||
48 | deriving (Show, Eq) | ||
49 | |||
50 | data 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 | |||
60 | instance EventSource Handle where | ||
61 | data Event Handle = StatusChanged HandleStatus | ||
62 | listen Handle {..} = CS.listen undefined | ||
63 | |||
64 | data 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 | |||
77 | instance Eq Client where | ||
78 | (==) = (==) `on` clientPeerId | ||
79 | |||
80 | instance Ord Client where | ||
81 | compare = comparing clientPeerId | ||
82 | |||
83 | instance 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'. | ||
90 | externalAddr :: Client -> PeerAddr (Maybe IP) | ||
91 | externalAddr 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 | |||
101 | newtype BitTorrent a = BitTorrent | ||
102 | { unBitTorrent :: ReaderT Client IO a | ||
103 | } deriving ( Functor, Applicative, Monad | ||
104 | , MonadIO, MonadThrow, MonadBase IO | ||
105 | ) | ||
106 | |||
107 | class MonadBitTorrent m where | ||
108 | liftBT :: BitTorrent a -> m a | ||
109 | |||
110 | #if MIN_VERSION_monad_control(1,0,0) | ||
111 | newtype BTStM a = BTStM { unBTSt :: StM (ReaderT Client IO) a } | ||
112 | |||
113 | instance 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 | ||
122 | instance 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. | ||
133 | instance MonadBitTorrent BitTorrent where | ||
134 | liftBT = id | ||
135 | |||
136 | instance 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' | ||
141 | instance 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. | ||
147 | instance MonadDHT BitTorrent where | ||
148 | liftDHT action = BitTorrent $ do | ||
149 | node <- asks clientNode | ||
150 | liftIO $ runDHT node action | ||
151 | |||
152 | instance MonadLogger BitTorrent where | ||
153 | monadLoggerLog loc src lvl msg = BitTorrent $ do | ||
154 | logger <- asks clientLogger | ||
155 | liftIO $ logger loc src lvl (toLogStr msg) | ||
156 | |||
157 | runBitTorrent :: Client -> BitTorrent a -> IO a | ||
158 | runBitTorrent client action = runReaderT (unBitTorrent action) client | ||
159 | {-# INLINE runBitTorrent #-} | ||
160 | |||
161 | getClient :: BitTorrent Client | ||
162 | getClient = BitTorrent ask | ||
163 | {-# INLINE getClient #-} | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange.hs b/bittorrent/src/Network/BitTorrent/Exchange.hs new file mode 100644 index 00000000..143bf090 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange.hs | |||
@@ -0,0 +1,35 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | module Network.BitTorrent.Exchange | ||
9 | ( -- * Manager | ||
10 | Options (..) | ||
11 | , Manager | ||
12 | , Handler | ||
13 | , newManager | ||
14 | , closeManager | ||
15 | |||
16 | -- * Session | ||
17 | , Caps | ||
18 | , Extension | ||
19 | , toCaps | ||
20 | , Session | ||
21 | , newSession | ||
22 | , closeSession | ||
23 | |||
24 | -- * Query | ||
25 | , waitMetadata | ||
26 | , takeMetadata | ||
27 | |||
28 | -- * Connections | ||
29 | , connect | ||
30 | , connectSink | ||
31 | ) where | ||
32 | |||
33 | import Network.BitTorrent.Exchange.Manager | ||
34 | import Network.BitTorrent.Exchange.Message | ||
35 | import Network.BitTorrent.Exchange.Session | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange/Bitfield.hs b/bittorrent/src/Network/BitTorrent/Exchange/Bitfield.hs new file mode 100644 index 00000000..7bae3475 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange/Bitfield.hs | |||
@@ -0,0 +1,399 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This modules provides all necessary machinery to work with | ||
9 | -- bitfields. Bitfields are used to keep track indices of complete | ||
10 | -- pieces either this peer have or remote peer have. | ||
11 | -- | ||
12 | -- There are also commonly used piece seletion algorithms | ||
13 | -- which used to find out which one next piece to download. | ||
14 | -- Selectors considered to be used in the following order: | ||
15 | -- | ||
16 | -- * 'randomFirst' - at the start of download. | ||
17 | -- | ||
18 | -- * 'rarestFirst' - performed to avoid situation when | ||
19 | -- rarest piece is unaccessible. | ||
20 | -- | ||
21 | -- * 'endGame' - performed after a peer has requested all | ||
22 | -- the subpieces of the content. | ||
23 | -- | ||
24 | -- Note that BitTorrent protocol recommend (TODO link?) the | ||
25 | -- 'strictFirst' priority policy for /subpiece/ or /blocks/ | ||
26 | -- selection. | ||
27 | -- | ||
28 | {-# LANGUAGE CPP #-} | ||
29 | {-# LANGUAGE BangPatterns #-} | ||
30 | {-# LANGUAGE RecordWildCards #-} | ||
31 | module Network.BitTorrent.Exchange.Bitfield | ||
32 | ( -- * Bitfield | ||
33 | PieceIx | ||
34 | , PieceCount | ||
35 | , Bitfield | ||
36 | |||
37 | -- * Construction | ||
38 | , haveAll | ||
39 | , haveNone | ||
40 | , have | ||
41 | , singleton | ||
42 | , interval | ||
43 | , adjustSize | ||
44 | |||
45 | -- * Query | ||
46 | -- ** Cardinality | ||
47 | , Network.BitTorrent.Exchange.Bitfield.null | ||
48 | , Network.BitTorrent.Exchange.Bitfield.full | ||
49 | , haveCount | ||
50 | , totalCount | ||
51 | , completeness | ||
52 | |||
53 | -- ** Membership | ||
54 | , member | ||
55 | , notMember | ||
56 | , findMin | ||
57 | , findMax | ||
58 | , isSubsetOf | ||
59 | |||
60 | -- ** Availability | ||
61 | , complement | ||
62 | , Frequency | ||
63 | , frequencies | ||
64 | , rarest | ||
65 | |||
66 | -- * Combine | ||
67 | , insert | ||
68 | , union | ||
69 | , intersection | ||
70 | , difference | ||
71 | |||
72 | -- * Conversion | ||
73 | , toList | ||
74 | , fromList | ||
75 | |||
76 | -- * Serialization | ||
77 | , fromBitmap | ||
78 | , toBitmap | ||
79 | |||
80 | -- * Piece selection | ||
81 | , Selector | ||
82 | , selector | ||
83 | , strategyClass | ||
84 | |||
85 | , strictFirst | ||
86 | , strictLast | ||
87 | , rarestFirst | ||
88 | , randomFirst | ||
89 | , endGame | ||
90 | ) where | ||
91 | |||
92 | import Control.Monad | ||
93 | import Control.Monad.ST | ||
94 | import Data.ByteString (ByteString) | ||
95 | import qualified Data.ByteString as B | ||
96 | import qualified Data.ByteString.Lazy as Lazy | ||
97 | import Data.Vector.Unboxed (Vector) | ||
98 | import qualified Data.Vector.Unboxed as V | ||
99 | import qualified Data.Vector.Unboxed.Mutable as VM | ||
100 | import Data.IntervalSet (IntSet) | ||
101 | import qualified Data.IntervalSet as S | ||
102 | import qualified Data.IntervalSet.ByteString as S | ||
103 | import Data.List (foldl') | ||
104 | import Data.Monoid | ||
105 | import Data.Ratio | ||
106 | |||
107 | import Data.Torrent | ||
108 | |||
109 | -- TODO cache some operations | ||
110 | |||
111 | -- | Bitfields are represented just as integer sets but with | ||
112 | -- restriction: the each set should be within given interval (or | ||
113 | -- subset of the specified interval). Size is used to specify | ||
114 | -- interval, so bitfield of size 10 might contain only indices in | ||
115 | -- interval [0..9]. | ||
116 | -- | ||
117 | data Bitfield = Bitfield { | ||
118 | bfSize :: !PieceCount | ||
119 | , bfSet :: !IntSet | ||
120 | } deriving (Show, Read, Eq) | ||
121 | |||
122 | -- Invariants: all elements of bfSet lie in [0..bfSize - 1]; | ||
123 | |||
124 | instance Monoid Bitfield where | ||
125 | {-# SPECIALIZE instance Monoid Bitfield #-} | ||
126 | mempty = haveNone 0 | ||
127 | mappend = union | ||
128 | mconcat = unions | ||
129 | |||
130 | {----------------------------------------------------------------------- | ||
131 | Construction | ||
132 | -----------------------------------------------------------------------} | ||
133 | |||
134 | -- | The empty bitfield of the given size. | ||
135 | haveNone :: PieceCount -> Bitfield | ||
136 | haveNone s = Bitfield s S.empty | ||
137 | |||
138 | -- | The full bitfield containing all piece indices for the given size. | ||
139 | haveAll :: PieceCount -> Bitfield | ||
140 | haveAll s = Bitfield s (S.interval 0 (s - 1)) | ||
141 | |||
142 | -- | Insert the index in the set ignoring out of range indices. | ||
143 | have :: PieceIx -> Bitfield -> Bitfield | ||
144 | have ix Bitfield {..} | ||
145 | | 0 <= ix && ix < bfSize = Bitfield bfSize (S.insert ix bfSet) | ||
146 | | otherwise = Bitfield bfSize bfSet | ||
147 | |||
148 | singleton :: PieceIx -> PieceCount -> Bitfield | ||
149 | singleton ix pc = have ix (haveNone pc) | ||
150 | |||
151 | -- | Assign new size to bitfield. FIXME Normally, size should be only | ||
152 | -- decreased, otherwise exception raised. | ||
153 | adjustSize :: PieceCount -> Bitfield -> Bitfield | ||
154 | adjustSize s Bitfield {..} = Bitfield s bfSet | ||
155 | |||
156 | -- | NOTE: for internal use only | ||
157 | interval :: PieceCount -> PieceIx -> PieceIx -> Bitfield | ||
158 | interval pc a b = Bitfield pc (S.interval a b) | ||
159 | |||
160 | {----------------------------------------------------------------------- | ||
161 | Query | ||
162 | -----------------------------------------------------------------------} | ||
163 | |||
164 | -- | Test if bitifield have no one index: peer do not have anything. | ||
165 | null :: Bitfield -> Bool | ||
166 | null Bitfield {..} = S.null bfSet | ||
167 | |||
168 | -- | Test if bitfield have all pieces. | ||
169 | full :: Bitfield -> Bool | ||
170 | full Bitfield {..} = S.size bfSet == bfSize | ||
171 | |||
172 | -- | Count of peer have pieces. | ||
173 | haveCount :: Bitfield -> PieceCount | ||
174 | haveCount = S.size . bfSet | ||
175 | |||
176 | -- | Total count of pieces and its indices. | ||
177 | totalCount :: Bitfield -> PieceCount | ||
178 | totalCount = bfSize | ||
179 | |||
180 | -- | Ratio of /have/ piece count to the /total/ piece count. | ||
181 | -- | ||
182 | -- > forall bf. 0 <= completeness bf <= 1 | ||
183 | -- | ||
184 | completeness :: Bitfield -> Ratio PieceCount | ||
185 | completeness b = haveCount b % totalCount b | ||
186 | |||
187 | inRange :: PieceIx -> Bitfield -> Bool | ||
188 | inRange ix Bitfield {..} = 0 <= ix && ix < bfSize | ||
189 | |||
190 | member :: PieceIx -> Bitfield -> Bool | ||
191 | member ix bf @ Bitfield {..} | ||
192 | | ix `inRange` bf = ix `S.member` bfSet | ||
193 | | otherwise = False | ||
194 | |||
195 | notMember :: PieceIx -> Bitfield -> Bool | ||
196 | notMember ix bf @ Bitfield {..} | ||
197 | | ix `inRange` bf = ix `S.notMember` bfSet | ||
198 | | otherwise = True | ||
199 | |||
200 | -- | Find first available piece index. | ||
201 | findMin :: Bitfield -> PieceIx | ||
202 | findMin = S.findMin . bfSet | ||
203 | {-# INLINE findMin #-} | ||
204 | |||
205 | -- | Find last available piece index. | ||
206 | findMax :: Bitfield -> PieceIx | ||
207 | findMax = S.findMax . bfSet | ||
208 | {-# INLINE findMax #-} | ||
209 | |||
210 | -- | Check if all pieces from first bitfield present if the second bitfield | ||
211 | isSubsetOf :: Bitfield -> Bitfield -> Bool | ||
212 | isSubsetOf a b = bfSet a `S.isSubsetOf` bfSet b | ||
213 | {-# INLINE isSubsetOf #-} | ||
214 | |||
215 | -- | Resulting bitfield includes only missing pieces. | ||
216 | complement :: Bitfield -> Bitfield | ||
217 | complement Bitfield {..} = Bitfield | ||
218 | { bfSet = uni `S.difference` bfSet | ||
219 | , bfSize = bfSize | ||
220 | } | ||
221 | where | ||
222 | Bitfield _ uni = haveAll bfSize | ||
223 | {-# INLINE complement #-} | ||
224 | |||
225 | {----------------------------------------------------------------------- | ||
226 | -- Availability | ||
227 | -----------------------------------------------------------------------} | ||
228 | |||
229 | -- | Frequencies are needed in piece selection startegies which use | ||
230 | -- availability quantity to find out the optimal next piece index to | ||
231 | -- download. | ||
232 | type Frequency = Int | ||
233 | |||
234 | -- TODO rename to availability | ||
235 | -- | How many times each piece index occur in the given bitfield set. | ||
236 | frequencies :: [Bitfield] -> Vector Frequency | ||
237 | frequencies [] = V.fromList [] | ||
238 | frequencies xs = runST $ do | ||
239 | v <- VM.new size | ||
240 | VM.set v 0 | ||
241 | forM_ xs $ \ Bitfield {..} -> do | ||
242 | forM_ (S.toList bfSet) $ \ x -> do | ||
243 | fr <- VM.read v x | ||
244 | VM.write v x (succ fr) | ||
245 | V.unsafeFreeze v | ||
246 | where | ||
247 | size = maximum (map bfSize xs) | ||
248 | |||
249 | -- TODO it seems like this operation is veeery slow | ||
250 | |||
251 | -- | Find least available piece index. If no piece available return | ||
252 | -- 'Nothing'. | ||
253 | rarest :: [Bitfield] -> Maybe PieceIx | ||
254 | rarest xs | ||
255 | | V.null freqMap = Nothing | ||
256 | | otherwise | ||
257 | = Just $ fst $ V.ifoldr' minIx (0, freqMap V.! 0) freqMap | ||
258 | where | ||
259 | freqMap = frequencies xs | ||
260 | |||
261 | minIx :: PieceIx -> Frequency | ||
262 | -> (PieceIx, Frequency) | ||
263 | -> (PieceIx, Frequency) | ||
264 | minIx ix fr acc@(_, fra) | ||
265 | | fr < fra && fr > 0 = (ix, fr) | ||
266 | | otherwise = acc | ||
267 | |||
268 | |||
269 | {----------------------------------------------------------------------- | ||
270 | Combine | ||
271 | -----------------------------------------------------------------------} | ||
272 | |||
273 | insert :: PieceIx -> Bitfield -> Bitfield | ||
274 | insert pix bf @ Bitfield {..} | ||
275 | | 0 <= pix && pix < bfSize = Bitfield | ||
276 | { bfSet = S.insert pix bfSet | ||
277 | , bfSize = bfSize | ||
278 | } | ||
279 | | otherwise = bf | ||
280 | |||
281 | -- | Find indices at least one peer have. | ||
282 | union :: Bitfield -> Bitfield -> Bitfield | ||
283 | union a b = {-# SCC union #-} Bitfield { | ||
284 | bfSize = bfSize a `max` bfSize b | ||
285 | , bfSet = bfSet a `S.union` bfSet b | ||
286 | } | ||
287 | |||
288 | -- | Find indices both peers have. | ||
289 | intersection :: Bitfield -> Bitfield -> Bitfield | ||
290 | intersection a b = {-# SCC intersection #-} Bitfield { | ||
291 | bfSize = bfSize a `min` bfSize b | ||
292 | , bfSet = bfSet a `S.intersection` bfSet b | ||
293 | } | ||
294 | |||
295 | -- | Find indices which have first peer but do not have the second peer. | ||
296 | difference :: Bitfield -> Bitfield -> Bitfield | ||
297 | difference a b = {-# SCC difference #-} Bitfield { | ||
298 | bfSize = bfSize a -- FIXME is it reasonable? | ||
299 | , bfSet = bfSet a `S.difference` bfSet b | ||
300 | } | ||
301 | |||
302 | -- | Find indices the any of the peers have. | ||
303 | unions :: [Bitfield] -> Bitfield | ||
304 | unions = {-# SCC unions #-} foldl' union (haveNone 0) | ||
305 | |||
306 | {----------------------------------------------------------------------- | ||
307 | Serialization | ||
308 | -----------------------------------------------------------------------} | ||
309 | |||
310 | -- | List all /have/ indexes. | ||
311 | toList :: Bitfield -> [PieceIx] | ||
312 | toList Bitfield {..} = S.toList bfSet | ||
313 | |||
314 | -- | Make bitfield from list of /have/ indexes. | ||
315 | fromList :: PieceCount -> [PieceIx] -> Bitfield | ||
316 | fromList s ixs = Bitfield { | ||
317 | bfSize = s | ||
318 | , bfSet = S.splitGT (-1) $ S.splitLT s $ S.fromList ixs | ||
319 | } | ||
320 | |||
321 | -- | Unpack 'Bitfield' from tightly packed bit array. Note resulting | ||
322 | -- size might be more than real bitfield size, use 'adjustSize'. | ||
323 | fromBitmap :: ByteString -> Bitfield | ||
324 | fromBitmap bs = {-# SCC fromBitmap #-} Bitfield { | ||
325 | bfSize = B.length bs * 8 | ||
326 | , bfSet = S.fromByteString bs | ||
327 | } | ||
328 | {-# INLINE fromBitmap #-} | ||
329 | |||
330 | -- | Pack a 'Bitfield' to tightly packed bit array. | ||
331 | toBitmap :: Bitfield -> Lazy.ByteString | ||
332 | toBitmap Bitfield {..} = {-# SCC toBitmap #-} Lazy.fromChunks [intsetBM, alignment] | ||
333 | where | ||
334 | byteSize = bfSize `div` 8 + if bfSize `mod` 8 == 0 then 0 else 1 | ||
335 | alignment = B.replicate (byteSize - B.length intsetBM) 0 | ||
336 | intsetBM = S.toByteString bfSet | ||
337 | |||
338 | {----------------------------------------------------------------------- | ||
339 | -- Piece selection | ||
340 | -----------------------------------------------------------------------} | ||
341 | |||
342 | type Selector = Bitfield -- ^ Indices of client /have/ pieces. | ||
343 | -> Bitfield -- ^ Indices of peer /have/ pieces. | ||
344 | -> [Bitfield] -- ^ Indices of other peers /have/ pieces. | ||
345 | -> Maybe PieceIx -- ^ Zero-based index of piece to request | ||
346 | -- to, if any. | ||
347 | |||
348 | selector :: Selector -- ^ Selector to use at the start. | ||
349 | -> Ratio PieceCount | ||
350 | -> Selector -- ^ Selector to use after the client have | ||
351 | -- the C pieces. | ||
352 | -> Selector -- ^ Selector that changes behaviour based | ||
353 | -- on completeness. | ||
354 | selector start pt ready h a xs = | ||
355 | case strategyClass pt h of | ||
356 | SCBeginning -> start h a xs | ||
357 | SCReady -> ready h a xs | ||
358 | SCEnd -> endGame h a xs | ||
359 | |||
360 | data StartegyClass | ||
361 | = SCBeginning | ||
362 | | SCReady | ||
363 | | SCEnd | ||
364 | deriving (Show, Eq, Ord, Enum, Bounded) | ||
365 | |||
366 | |||
367 | strategyClass :: Ratio PieceCount -> Bitfield -> StartegyClass | ||
368 | strategyClass threshold = classify . completeness | ||
369 | where | ||
370 | classify c | ||
371 | | c < threshold = SCBeginning | ||
372 | | c + 1 % numerator c < 1 = SCReady | ||
373 | -- FIXME numerator have is not total count | ||
374 | | otherwise = SCEnd | ||
375 | |||
376 | |||
377 | -- | Select the first available piece. | ||
378 | strictFirst :: Selector | ||
379 | strictFirst h a _ = Just $ findMin (difference a h) | ||
380 | |||
381 | -- | Select the last available piece. | ||
382 | strictLast :: Selector | ||
383 | strictLast h a _ = Just $ findMax (difference a h) | ||
384 | |||
385 | -- | | ||
386 | rarestFirst :: Selector | ||
387 | rarestFirst h a xs = rarest (map (intersection want) xs) | ||
388 | where | ||
389 | want = difference h a | ||
390 | |||
391 | -- | In average random first is faster than rarest first strategy but | ||
392 | -- only if all pieces are available. | ||
393 | randomFirst :: Selector | ||
394 | randomFirst = do | ||
395 | -- randomIO | ||
396 | error "randomFirst" | ||
397 | |||
398 | endGame :: Selector | ||
399 | endGame = strictLast | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange/Block.hs b/bittorrent/src/Network/BitTorrent/Exchange/Block.hs new file mode 100644 index 00000000..bc9a3d24 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange/Block.hs | |||
@@ -0,0 +1,369 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Blocks are used to transfer pieces. | ||
9 | -- | ||
10 | {-# LANGUAGE BangPatterns #-} | ||
11 | {-# LANGUAGE FlexibleInstances #-} | ||
12 | {-# LANGUAGE TemplateHaskell #-} | ||
13 | {-# LANGUAGE DeriveFunctor #-} | ||
14 | {-# LANGUAGE DeriveDataTypeable #-} | ||
15 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
16 | module Network.BitTorrent.Exchange.Block | ||
17 | ( -- * Block attributes | ||
18 | BlockOffset | ||
19 | , BlockCount | ||
20 | , BlockSize | ||
21 | , defaultTransferSize | ||
22 | |||
23 | -- * Block index | ||
24 | , BlockIx(..) | ||
25 | , blockIxRange | ||
26 | |||
27 | -- * Block data | ||
28 | , Block(..) | ||
29 | , blockIx | ||
30 | , blockSize | ||
31 | , blockRange | ||
32 | , isPiece | ||
33 | , leadingBlock | ||
34 | |||
35 | -- * Block bucket | ||
36 | , Bucket | ||
37 | |||
38 | -- ** Query | ||
39 | , Network.BitTorrent.Exchange.Block.null | ||
40 | , Network.BitTorrent.Exchange.Block.full | ||
41 | , Network.BitTorrent.Exchange.Block.size | ||
42 | , Network.BitTorrent.Exchange.Block.spans | ||
43 | |||
44 | -- ** Construction | ||
45 | , Network.BitTorrent.Exchange.Block.empty | ||
46 | , Network.BitTorrent.Exchange.Block.insert | ||
47 | , Network.BitTorrent.Exchange.Block.insertLazy | ||
48 | , Network.BitTorrent.Exchange.Block.merge | ||
49 | , Network.BitTorrent.Exchange.Block.fromList | ||
50 | |||
51 | -- ** Rendering | ||
52 | , Network.BitTorrent.Exchange.Block.toPiece | ||
53 | |||
54 | -- ** Debug | ||
55 | , Network.BitTorrent.Exchange.Block.valid | ||
56 | ) where | ||
57 | |||
58 | import Prelude hiding (span) | ||
59 | import Control.Applicative | ||
60 | import Data.ByteString as BS hiding (span) | ||
61 | import Data.ByteString.Lazy as BL hiding (span) | ||
62 | import Data.ByteString.Lazy.Builder as BS | ||
63 | import Data.Default | ||
64 | import Data.Monoid | ||
65 | import Data.List as L hiding (span) | ||
66 | import Data.Serialize as S | ||
67 | import Data.Typeable | ||
68 | import Numeric | ||
69 | import Text.PrettyPrint as PP hiding ((<>)) | ||
70 | import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) | ||
71 | |||
72 | import Data.Torrent | ||
73 | |||
74 | {----------------------------------------------------------------------- | ||
75 | -- Block attributes | ||
76 | -----------------------------------------------------------------------} | ||
77 | |||
78 | -- | Offset of a block in a piece in bytes. Should be multiple of | ||
79 | -- the choosen block size. | ||
80 | type BlockOffset = Int | ||
81 | |||
82 | -- | Size of a block in bytes. Should be power of 2. | ||
83 | -- | ||
84 | -- Normally block size is equal to 'defaultTransferSize'. | ||
85 | -- | ||
86 | type BlockSize = Int | ||
87 | |||
88 | -- | Number of block in a piece of a torrent. Used to distinguish | ||
89 | -- block count from piece count. | ||
90 | type BlockCount = Int | ||
91 | |||
92 | -- | Widely used semi-official block size. Some clients can ignore if | ||
93 | -- block size of BlockIx in Request message is not equal to this | ||
94 | -- value. | ||
95 | -- | ||
96 | defaultTransferSize :: BlockSize | ||
97 | defaultTransferSize = 16 * 1024 | ||
98 | |||
99 | {----------------------------------------------------------------------- | ||
100 | Block Index | ||
101 | -----------------------------------------------------------------------} | ||
102 | |||
103 | -- | BlockIx correspond. | ||
104 | data BlockIx = BlockIx { | ||
105 | -- | Zero-based piece index. | ||
106 | ixPiece :: {-# UNPACK #-} !PieceIx | ||
107 | |||
108 | -- | Zero-based byte offset within the piece. | ||
109 | , ixOffset :: {-# UNPACK #-} !BlockOffset | ||
110 | |||
111 | -- | Block size starting from offset. | ||
112 | , ixLength :: {-# UNPACK #-} !BlockSize | ||
113 | } deriving (Show, Eq, Typeable) | ||
114 | |||
115 | -- | First block in torrent. Useful for debugging. | ||
116 | instance Default BlockIx where | ||
117 | def = BlockIx 0 0 defaultTransferSize | ||
118 | |||
119 | getInt :: S.Get Int | ||
120 | getInt = fromIntegral <$> S.getWord32be | ||
121 | {-# INLINE getInt #-} | ||
122 | |||
123 | putInt :: S.Putter Int | ||
124 | putInt = S.putWord32be . fromIntegral | ||
125 | {-# INLINE putInt #-} | ||
126 | |||
127 | instance Serialize BlockIx where | ||
128 | {-# SPECIALIZE instance Serialize BlockIx #-} | ||
129 | get = BlockIx <$> getInt | ||
130 | <*> getInt | ||
131 | <*> getInt | ||
132 | {-# INLINE get #-} | ||
133 | |||
134 | put BlockIx {..} = do | ||
135 | putInt ixPiece | ||
136 | putInt ixOffset | ||
137 | putInt ixLength | ||
138 | {-# INLINE put #-} | ||
139 | |||
140 | instance Pretty BlockIx where | ||
141 | pPrint BlockIx {..} = | ||
142 | ("piece = " <> int ixPiece <> ",") <+> | ||
143 | ("offset = " <> int ixOffset <> ",") <+> | ||
144 | ("length = " <> int ixLength) | ||
145 | |||
146 | -- | Get location of payload bytes in the torrent content. | ||
147 | blockIxRange :: (Num a, Integral a) => PieceSize -> BlockIx -> (a, a) | ||
148 | blockIxRange piSize BlockIx {..} = (offset, offset + len) | ||
149 | where | ||
150 | offset = fromIntegral piSize * fromIntegral ixPiece | ||
151 | + fromIntegral ixOffset | ||
152 | len = fromIntegral ixLength | ||
153 | {-# INLINE blockIxRange #-} | ||
154 | |||
155 | {----------------------------------------------------------------------- | ||
156 | Block | ||
157 | -----------------------------------------------------------------------} | ||
158 | |||
159 | data Block payload = Block { | ||
160 | -- | Zero-based piece index. | ||
161 | blkPiece :: {-# UNPACK #-} !PieceIx | ||
162 | |||
163 | -- | Zero-based byte offset within the piece. | ||
164 | , blkOffset :: {-# UNPACK #-} !BlockOffset | ||
165 | |||
166 | -- | Payload bytes. | ||
167 | , blkData :: !payload | ||
168 | } deriving (Show, Eq, Functor, Typeable) | ||
169 | |||
170 | -- | Payload is ommitted. | ||
171 | instance Pretty (Block BL.ByteString) where | ||
172 | pPrint = pPrint . blockIx | ||
173 | {-# INLINE pPrint #-} | ||
174 | |||
175 | -- | Get size of block /payload/ in bytes. | ||
176 | blockSize :: Block BL.ByteString -> BlockSize | ||
177 | blockSize = fromIntegral . BL.length . blkData | ||
178 | {-# INLINE blockSize #-} | ||
179 | |||
180 | -- | Get block index of a block. | ||
181 | blockIx :: Block BL.ByteString -> BlockIx | ||
182 | blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize | ||
183 | |||
184 | -- | Get location of payload bytes in the torrent content. | ||
185 | blockRange :: (Num a, Integral a) | ||
186 | => PieceSize -> Block BL.ByteString -> (a, a) | ||
187 | blockRange piSize = blockIxRange piSize . blockIx | ||
188 | {-# INLINE blockRange #-} | ||
189 | |||
190 | -- | Test if a block can be safely turned into a piece. | ||
191 | isPiece :: PieceSize -> Block BL.ByteString -> Bool | ||
192 | isPiece pieceLen blk @ (Block i offset _) = | ||
193 | offset == 0 && blockSize blk == pieceLen && i >= 0 | ||
194 | {-# INLINE isPiece #-} | ||
195 | |||
196 | -- | First block in the piece. | ||
197 | leadingBlock :: PieceIx -> BlockSize -> BlockIx | ||
198 | leadingBlock pix blockSize = BlockIx | ||
199 | { ixPiece = pix | ||
200 | , ixOffset = 0 | ||
201 | , ixLength = blockSize | ||
202 | } | ||
203 | {-# INLINE leadingBlock #-} | ||
204 | |||
205 | {----------------------------------------------------------------------- | ||
206 | -- Bucket | ||
207 | -----------------------------------------------------------------------} | ||
208 | |||
209 | type Pos = Int | ||
210 | type ChunkSize = Int | ||
211 | |||
212 | -- | A sparse set of blocks used to represent an /in progress/ piece. | ||
213 | data Bucket | ||
214 | = Nil | ||
215 | | Span {-# UNPACK #-} !ChunkSize !Bucket | ||
216 | | Fill {-# UNPACK #-} !ChunkSize !Builder !Bucket | ||
217 | |||
218 | instance Show Bucket where | ||
219 | showsPrec i Nil = showString "" | ||
220 | showsPrec i (Span s xs) = showString "Span " <> showInt s | ||
221 | <> showString " " <> showsPrec i xs | ||
222 | showsPrec i (Fill s _ xs) = showString "Fill " <> showInt s | ||
223 | <> showString " " <> showsPrec i xs | ||
224 | |||
225 | -- | INVARIANT: 'Nil' should appear only after 'Span' of 'Fill'. | ||
226 | nilInvFailed :: a | ||
227 | nilInvFailed = error "Nil: bucket invariant failed" | ||
228 | |||
229 | valid :: Bucket -> Bool | ||
230 | valid = check Nothing | ||
231 | where | ||
232 | check Nothing Nil = False -- see 'nilInvFailed' | ||
233 | check (Just _) _ = True | ||
234 | check prevIsSpan (Span sz xs) = | ||
235 | prevIsSpan /= Just True && -- Span n (NotSpan .. ) invariant | ||
236 | sz > 0 && -- Span is always non-empty | ||
237 | check (Just True) xs | ||
238 | check prevIsSpan (Fill sz b xs) = | ||
239 | prevIsSpan /= Just True && -- Fill n (NotFill .. ) invariant | ||
240 | sz > 0 && -- Fill is always non-empty | ||
241 | check (Just False) xs | ||
242 | |||
243 | instance Pretty Bucket where | ||
244 | pPrint Nil = nilInvFailed | ||
245 | pPrint bkt = go bkt | ||
246 | where | ||
247 | go Nil = PP.empty | ||
248 | go (Span sz xs) = "Span" <+> PP.int sz <+> go xs | ||
249 | go (Fill sz b xs) = "Fill" <+> PP.int sz <+> go xs | ||
250 | |||
251 | -- | Smart constructor: use it when some block is /deleted/ from | ||
252 | -- bucket. | ||
253 | span :: ChunkSize -> Bucket -> Bucket | ||
254 | span sz (Span sz' xs) = Span (sz + sz') xs | ||
255 | span sz xxs = Span sz xxs | ||
256 | {-# INLINE span #-} | ||
257 | |||
258 | -- | Smart constructor: use it when some block is /inserted/ to | ||
259 | -- bucket. | ||
260 | fill :: ChunkSize -> Builder -> Bucket -> Bucket | ||
261 | fill sz b (Fill sz' b' xs) = Fill (sz + sz') (b <> b') xs | ||
262 | fill sz b xxs = Fill sz b xxs | ||
263 | {-# INLINE fill #-} | ||
264 | |||
265 | {----------------------------------------------------------------------- | ||
266 | -- Bucket queries | ||
267 | -----------------------------------------------------------------------} | ||
268 | |||
269 | -- | /O(1)/. Test if this bucket is empty. | ||
270 | null :: Bucket -> Bool | ||
271 | null Nil = nilInvFailed | ||
272 | null (Span _ Nil) = True | ||
273 | null _ = False | ||
274 | {-# INLINE null #-} | ||
275 | |||
276 | -- | /O(1)/. Test if this bucket is complete. | ||
277 | full :: Bucket -> Bool | ||
278 | full Nil = nilInvFailed | ||
279 | full (Fill _ _ Nil) = True | ||
280 | full _ = False | ||
281 | {-# INLINE full #-} | ||
282 | |||
283 | -- | /O(n)/. Total size of the incompleted piece. | ||
284 | size :: Bucket -> PieceSize | ||
285 | size Nil = nilInvFailed | ||
286 | size bkt = go bkt | ||
287 | where | ||
288 | go Nil = 0 | ||
289 | go (Span sz xs) = sz + go xs | ||
290 | go (Fill sz _ xs) = sz + go xs | ||
291 | |||
292 | -- | /O(n)/. List incomplete blocks to download. If some block have | ||
293 | -- size more than the specified 'BlockSize' then block is split into | ||
294 | -- smaller blocks to satisfy given 'BlockSize'. Small (for | ||
295 | -- e.g. trailing) blocks is not ignored, but returned in-order. | ||
296 | spans :: BlockSize -> Bucket -> [(BlockOffset, BlockSize)] | ||
297 | spans expectedSize = go 0 | ||
298 | where | ||
299 | go _ Nil = [] | ||
300 | go off (Span sz xs) = listChunks off sz ++ go (off + sz) xs | ||
301 | go off (Fill sz _ xs) = go (off + sz) xs | ||
302 | |||
303 | listChunks off restSize | ||
304 | | restSize <= 0 = [] | ||
305 | | otherwise = (off, blkSize) | ||
306 | : listChunks (off + blkSize) (restSize - blkSize) | ||
307 | where | ||
308 | blkSize = min expectedSize restSize | ||
309 | |||
310 | {----------------------------------------------------------------------- | ||
311 | -- Bucket contstruction | ||
312 | -----------------------------------------------------------------------} | ||
313 | |||
314 | -- | /O(1)/. A new empty bucket capable to alloof specified size. | ||
315 | empty :: PieceSize -> Bucket | ||
316 | empty sz | ||
317 | | sz < 0 = error "empty: Bucket size must be a non-negative value" | ||
318 | | otherwise = Span sz Nil | ||
319 | {-# INLINE empty #-} | ||
320 | |||
321 | insertSpan :: Pos -> BS.ByteString -> ChunkSize -> Bucket -> Bucket | ||
322 | insertSpan !pos !bs !span_sz !xs = | ||
323 | let pref_len = pos | ||
324 | fill_len = span_sz - pos `min` BS.length bs | ||
325 | suff_len = (span_sz - pos) - fill_len | ||
326 | in mkSpan pref_len $ | ||
327 | fill fill_len (byteString (BS.take fill_len bs)) $ | ||
328 | mkSpan suff_len $ | ||
329 | xs | ||
330 | where | ||
331 | mkSpan 0 xs = xs | ||
332 | mkSpan sz xs = Span sz xs | ||
333 | |||
334 | -- | /O(n)/. Insert a strict bytestring at specified position. | ||
335 | -- | ||
336 | -- Best case: if blocks are inserted in sequential order, then this | ||
337 | -- operation should take /O(1)/. | ||
338 | -- | ||
339 | insert :: Pos -> BS.ByteString -> Bucket -> Bucket | ||
340 | insert _ _ Nil = nilInvFailed | ||
341 | insert dstPos bs bucket = go 0 bucket | ||
342 | where | ||
343 | intersects curPos sz = dstPos >= curPos && dstPos <= curPos + sz | ||
344 | |||
345 | go _ Nil = Nil | ||
346 | go curPos (Span sz xs) | ||
347 | | intersects curPos sz = insertSpan (dstPos - curPos) bs sz xs | ||
348 | | otherwise = span sz (go (curPos + sz) xs) | ||
349 | go curPos bkt @ (Fill sz br xs) | ||
350 | | intersects curPos sz = bkt | ||
351 | | otherwise = fill sz br (go (curPos + sz) xs) | ||
352 | |||
353 | fromList :: PieceSize -> [(Pos, BS.ByteString)] -> Bucket | ||
354 | fromList s = L.foldr (uncurry Network.BitTorrent.Exchange.Block.insert) | ||
355 | (Network.BitTorrent.Exchange.Block.empty s) | ||
356 | |||
357 | -- TODO zero-copy | ||
358 | insertLazy :: Pos -> BL.ByteString -> Bucket -> Bucket | ||
359 | insertLazy pos bl = Network.BitTorrent.Exchange.Block.insert pos (BL.toStrict bl) | ||
360 | |||
361 | -- | /O(n)/. | ||
362 | merge :: Bucket -> Bucket -> Bucket | ||
363 | merge = error "Bucket.merge: not implemented" | ||
364 | |||
365 | -- | /O(1)/. | ||
366 | toPiece :: Bucket -> Maybe BL.ByteString | ||
367 | toPiece Nil = nilInvFailed | ||
368 | toPiece (Fill _ b Nil) = Just (toLazyByteString b) | ||
369 | toPiece _ = Nothing | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange/Connection.hs b/bittorrent/src/Network/BitTorrent/Exchange/Connection.hs new file mode 100644 index 00000000..6804d0a2 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange/Connection.hs | |||
@@ -0,0 +1,1012 @@ | |||
1 | -- | | ||
2 | -- Module : Network.BitTorrent.Exchange.Wire | ||
3 | -- Copyright : (c) Sam Truzjan 2013 | ||
4 | -- (c) Daniel Gröber 2013 | ||
5 | -- License : BSD3 | ||
6 | -- Maintainer : pxqr.sta@gmail.com | ||
7 | -- Stability : experimental | ||
8 | -- Portability : portable | ||
9 | -- | ||
10 | -- Each peer wire connection is identified by triple @(topic, | ||
11 | -- remote_addr, this_addr)@. This means that connections are the | ||
12 | -- same if and only if their 'ConnectionId' are the same. Of course, | ||
13 | -- you /must/ avoid duplicated connections. | ||
14 | -- | ||
15 | -- This module control /integrity/ of data send and received. | ||
16 | -- | ||
17 | {-# LANGUAGE DeriveDataTypeable #-} | ||
18 | {-# LANGUAGE TemplateHaskell #-} | ||
19 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
20 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
21 | module Network.BitTorrent.Exchange.Connection | ||
22 | ( -- * Wire | ||
23 | Connected | ||
24 | , Wire | ||
25 | , ChannelSide (..) | ||
26 | |||
27 | -- * Connection | ||
28 | , Connection | ||
29 | , connInitiatedBy | ||
30 | |||
31 | -- ** Identity | ||
32 | , connRemoteAddr | ||
33 | , connTopic | ||
34 | , connRemotePeerId | ||
35 | , connThisPeerId | ||
36 | |||
37 | -- ** Capabilities | ||
38 | , connProtocol | ||
39 | , connCaps | ||
40 | , connExtCaps | ||
41 | , connRemoteEhs | ||
42 | |||
43 | -- ** State | ||
44 | , connStatus | ||
45 | , connBitfield | ||
46 | |||
47 | -- ** Env | ||
48 | , connOptions | ||
49 | , connSession | ||
50 | , connStats | ||
51 | |||
52 | -- ** Status | ||
53 | , PeerStatus (..) | ||
54 | , ConnectionStatus (..) | ||
55 | , updateStatus | ||
56 | , statusUpdates | ||
57 | , clientStatus | ||
58 | , remoteStatus | ||
59 | , canUpload | ||
60 | , canDownload | ||
61 | , defaultUnchokeSlots | ||
62 | , defaultRechokeInterval | ||
63 | |||
64 | |||
65 | -- * Setup | ||
66 | , ConnectionPrefs (..) | ||
67 | , SessionLink (..) | ||
68 | , ConnectionConfig (..) | ||
69 | |||
70 | -- ** Initiate | ||
71 | , connectWire | ||
72 | |||
73 | -- ** Accept | ||
74 | , PendingConnection | ||
75 | , newPendingConnection | ||
76 | , pendingPeer | ||
77 | , pendingCaps | ||
78 | , pendingTopic | ||
79 | , closePending | ||
80 | , acceptWire | ||
81 | |||
82 | -- ** Post setup actions | ||
83 | , resizeBitfield | ||
84 | |||
85 | -- * Messaging | ||
86 | , recvMessage | ||
87 | , sendMessage | ||
88 | , filterQueue | ||
89 | , getMaxQueueLength | ||
90 | |||
91 | -- * Exceptions | ||
92 | , ProtocolError (..) | ||
93 | , WireFailure (..) | ||
94 | , peerPenalty | ||
95 | , isWireFailure | ||
96 | , disconnectPeer | ||
97 | |||
98 | -- * Stats | ||
99 | , ByteStats (..) | ||
100 | , FlowStats (..) | ||
101 | , ConnectionStats (..) | ||
102 | |||
103 | -- * Flood detection | ||
104 | , FloodDetector (..) | ||
105 | |||
106 | -- * Options | ||
107 | , Options (..) | ||
108 | ) where | ||
109 | |||
110 | import Control.Applicative | ||
111 | import Control.Concurrent hiding (yield) | ||
112 | import Control.Exception | ||
113 | import Control.Monad.Reader | ||
114 | import Control.Monad.State | ||
115 | import Control.Monad.Trans.Resource | ||
116 | import Control.Lens | ||
117 | import Data.ByteString as BS | ||
118 | import Data.ByteString.Lazy as BSL | ||
119 | import Data.Conduit as C | ||
120 | import Data.Conduit.Cereal | ||
121 | import Data.Conduit.List | ||
122 | import Data.Conduit.Network | ||
123 | import Data.Default | ||
124 | import Data.IORef | ||
125 | import Data.List as L | ||
126 | import Data.Maybe as M | ||
127 | import Data.Monoid | ||
128 | import Data.Serialize as S | ||
129 | import Data.Typeable | ||
130 | import Network | ||
131 | import Network.Socket hiding (Connected) | ||
132 | import Network.Socket.ByteString as BS | ||
133 | import Text.PrettyPrint as PP hiding ((<>)) | ||
134 | import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) | ||
135 | import Text.Show.Functions () | ||
136 | import System.Log.FastLogger (ToLogStr(..)) | ||
137 | import System.Timeout | ||
138 | |||
139 | import Data.Torrent | ||
140 | import Network.Address | ||
141 | import Network.BitTorrent.Exchange.Bitfield as BF | ||
142 | import Network.BitTorrent.Exchange.Message as Msg | ||
143 | |||
144 | -- TODO handle port message? | ||
145 | -- TODO handle limits? | ||
146 | -- TODO filter not requested PIECE messages | ||
147 | -- TODO metadata piece request flood protection | ||
148 | -- TODO piece request flood protection | ||
149 | -- TODO protect against flood attacks | ||
150 | {----------------------------------------------------------------------- | ||
151 | -- Exceptions | ||
152 | -----------------------------------------------------------------------} | ||
153 | |||
154 | -- | Used to specify initiator of 'ProtocolError'. | ||
155 | data ChannelSide | ||
156 | = ThisPeer | ||
157 | | RemotePeer | ||
158 | deriving (Show, Eq, Enum, Bounded) | ||
159 | |||
160 | instance Default ChannelSide where | ||
161 | def = ThisPeer | ||
162 | |||
163 | instance Pretty ChannelSide where | ||
164 | pPrint = PP.text . show | ||
165 | |||
166 | -- | A protocol errors occur when a peer violates protocol | ||
167 | -- specification. | ||
168 | data ProtocolError | ||
169 | -- | Protocol string should be 'BitTorrent Protocol' but remote | ||
170 | -- peer have sent a different string. | ||
171 | = InvalidProtocol ProtocolName | ||
172 | |||
173 | -- | Sent and received protocol strings do not match. Can occur | ||
174 | -- in 'connectWire' only. | ||
175 | | UnexpectedProtocol ProtocolName | ||
176 | |||
177 | -- | /Remote/ peer replied with invalid 'hsInfoHash' which do not | ||
178 | -- match with 'hsInfoHash' /this/ peer have sent. Can occur in | ||
179 | -- 'connectWire' or 'acceptWire' only. | ||
180 | | UnexpectedTopic InfoHash | ||
181 | |||
182 | -- | Some trackers or DHT can return 'PeerId' of a peer. If a | ||
183 | -- remote peer handshaked with different 'hsPeerId' then this | ||
184 | -- exception is raised. Can occur in 'connectWire' only. | ||
185 | | UnexpectedPeerId PeerId | ||
186 | |||
187 | -- | Accepted peer have sent unknown torrent infohash in | ||
188 | -- 'hsInfoHash' field. This situation usually happen when /this/ | ||
189 | -- peer have deleted the requested torrent. The error can occur in | ||
190 | -- 'acceptWire' function only. | ||
191 | | UnknownTopic InfoHash | ||
192 | |||
193 | -- | A remote peer have 'ExtExtended' enabled but did not send an | ||
194 | -- 'ExtendedHandshake' back. | ||
195 | | HandshakeRefused | ||
196 | |||
197 | -- | 'Network.BitTorrent.Exchange.Message.Bitfield' message MUST | ||
198 | -- be send either once or zero times, but either this peer or | ||
199 | -- remote peer send a bitfield message the second time. | ||
200 | | BitfieldAlreadySent ChannelSide | ||
201 | |||
202 | -- | Capabilities violation. For example this exception can occur | ||
203 | -- when a peer have sent 'Port' message but 'ExtDHT' is not | ||
204 | -- allowed in 'connCaps'. | ||
205 | | DisallowedMessage | ||
206 | { -- | Who sent invalid message. | ||
207 | violentSender :: ChannelSide | ||
208 | |||
209 | -- | If the 'violentSender' reconnect with this extension | ||
210 | -- enabled then he can try to send this message. | ||
211 | , extensionRequired :: Extension | ||
212 | } | ||
213 | deriving Show | ||
214 | |||
215 | instance Pretty ProtocolError where | ||
216 | pPrint = PP.text . show | ||
217 | |||
218 | errorPenalty :: ProtocolError -> Int | ||
219 | errorPenalty (InvalidProtocol _) = 1 | ||
220 | errorPenalty (UnexpectedProtocol _) = 1 | ||
221 | errorPenalty (UnexpectedTopic _) = 1 | ||
222 | errorPenalty (UnexpectedPeerId _) = 1 | ||
223 | errorPenalty (UnknownTopic _) = 0 | ||
224 | errorPenalty (HandshakeRefused ) = 1 | ||
225 | errorPenalty (BitfieldAlreadySent _) = 1 | ||
226 | errorPenalty (DisallowedMessage _ _) = 1 | ||
227 | |||
228 | -- | Exceptions used to interrupt the current P2P session. | ||
229 | data WireFailure | ||
230 | = ConnectionRefused IOError | ||
231 | |||
232 | -- | Force termination of wire connection. | ||
233 | -- | ||
234 | -- Normally you should throw only this exception from event loop | ||
235 | -- using 'disconnectPeer', other exceptions are thrown | ||
236 | -- automatically by functions from this module. | ||
237 | -- | ||
238 | | DisconnectPeer | ||
239 | |||
240 | -- | A peer not responding and did not send a 'KeepAlive' message | ||
241 | -- for a specified period of time. | ||
242 | | PeerDisconnected | ||
243 | |||
244 | -- | A remote peer have sent some unknown message we unable to | ||
245 | -- parse. | ||
246 | | DecodingError GetException | ||
247 | |||
248 | -- | See 'ProtocolError' for more details. | ||
249 | | ProtocolError ProtocolError | ||
250 | |||
251 | -- | A possible malicious peer have sent too many control messages | ||
252 | -- without making any progress. | ||
253 | | FloodDetected ConnectionStats | ||
254 | deriving (Show, Typeable) | ||
255 | |||
256 | instance Exception WireFailure | ||
257 | |||
258 | instance Pretty WireFailure where | ||
259 | pPrint = PP.text . show | ||
260 | |||
261 | -- TODO | ||
262 | -- data Penalty = Ban | Penalty Int | ||
263 | |||
264 | peerPenalty :: WireFailure -> Int | ||
265 | peerPenalty DisconnectPeer = 0 | ||
266 | peerPenalty PeerDisconnected = 0 | ||
267 | peerPenalty (DecodingError _) = 1 | ||
268 | peerPenalty (ProtocolError e) = errorPenalty e | ||
269 | peerPenalty (FloodDetected _) = 1 | ||
270 | |||
271 | -- | Do nothing with exception, used with 'handle' or 'try'. | ||
272 | isWireFailure :: Monad m => WireFailure -> m () | ||
273 | isWireFailure _ = return () | ||
274 | |||
275 | protocolError :: MonadThrow m => ProtocolError -> m a | ||
276 | protocolError = monadThrow . ProtocolError | ||
277 | |||
278 | {----------------------------------------------------------------------- | ||
279 | -- Stats | ||
280 | -----------------------------------------------------------------------} | ||
281 | |||
282 | -- | Message stats in one direction. | ||
283 | data FlowStats = FlowStats | ||
284 | { -- | Number of the messages sent or received. | ||
285 | messageCount :: {-# UNPACK #-} !Int | ||
286 | -- | Sum of byte sequences of all messages. | ||
287 | , messageBytes :: {-# UNPACK #-} !ByteStats | ||
288 | } deriving Show | ||
289 | |||
290 | instance Pretty FlowStats where | ||
291 | pPrint FlowStats {..} = | ||
292 | PP.int messageCount <+> "messages" $+$ | ||
293 | pPrint messageBytes | ||
294 | |||
295 | -- | Zeroed stats. | ||
296 | instance Default FlowStats where | ||
297 | def = FlowStats 0 def | ||
298 | |||
299 | -- | Monoid under addition. | ||
300 | instance Monoid FlowStats where | ||
301 | mempty = def | ||
302 | mappend a b = FlowStats | ||
303 | { messageBytes = messageBytes a <> messageBytes b | ||
304 | , messageCount = messageCount a + messageCount b | ||
305 | } | ||
306 | |||
307 | -- | Find average length of byte sequences per message. | ||
308 | avgByteStats :: FlowStats -> ByteStats | ||
309 | avgByteStats (FlowStats n ByteStats {..}) = ByteStats | ||
310 | { overhead = overhead `quot` n | ||
311 | , control = control `quot` n | ||
312 | , payload = payload `quot` n | ||
313 | } | ||
314 | |||
315 | -- | Message stats in both directions. This data can be retrieved | ||
316 | -- using 'getStats' function. | ||
317 | -- | ||
318 | -- Note that this stats is completely different from | ||
319 | -- 'Data.Torrent.Progress.Progress': payload bytes not necessary | ||
320 | -- equal to downloaded\/uploaded bytes since a peer can send a | ||
321 | -- broken block. | ||
322 | -- | ||
323 | data ConnectionStats = ConnectionStats | ||
324 | { -- | Received messages stats. | ||
325 | incomingFlow :: !FlowStats | ||
326 | -- | Sent messages stats. | ||
327 | , outcomingFlow :: !FlowStats | ||
328 | } deriving Show | ||
329 | |||
330 | instance Pretty ConnectionStats where | ||
331 | pPrint ConnectionStats {..} = vcat | ||
332 | [ "Recv:" <+> pPrint incomingFlow | ||
333 | , "Sent:" <+> pPrint outcomingFlow | ||
334 | , "Both:" <+> pPrint (incomingFlow <> outcomingFlow) | ||
335 | ] | ||
336 | |||
337 | -- | Zeroed stats. | ||
338 | instance Default ConnectionStats where | ||
339 | def = ConnectionStats def def | ||
340 | |||
341 | -- | Monoid under addition. | ||
342 | instance Monoid ConnectionStats where | ||
343 | mempty = def | ||
344 | mappend a b = ConnectionStats | ||
345 | { incomingFlow = incomingFlow a <> incomingFlow b | ||
346 | , outcomingFlow = outcomingFlow a <> outcomingFlow b | ||
347 | } | ||
348 | |||
349 | -- | Aggregate one more message stats in the /specified/ direction. | ||
350 | addStats :: ChannelSide -> ByteStats -> ConnectionStats -> ConnectionStats | ||
351 | addStats ThisPeer x s = s { outcomingFlow = (FlowStats 1 x) <> (outcomingFlow s) } | ||
352 | addStats RemotePeer x s = s { incomingFlow = (FlowStats 1 x) <> (incomingFlow s) } | ||
353 | |||
354 | -- | Sum of overhead and control bytes in both directions. | ||
355 | wastedBytes :: ConnectionStats -> Int | ||
356 | wastedBytes ConnectionStats {..} = overhead + control | ||
357 | where | ||
358 | FlowStats _ ByteStats {..} = incomingFlow <> outcomingFlow | ||
359 | |||
360 | -- | Sum of payload bytes in both directions. | ||
361 | payloadBytes :: ConnectionStats -> Int | ||
362 | payloadBytes ConnectionStats {..} = | ||
363 | payload (messageBytes (incomingFlow <> outcomingFlow)) | ||
364 | |||
365 | -- | Sum of any bytes in both directions. | ||
366 | transmittedBytes :: ConnectionStats -> Int | ||
367 | transmittedBytes ConnectionStats {..} = | ||
368 | byteLength (messageBytes (incomingFlow <> outcomingFlow)) | ||
369 | |||
370 | {----------------------------------------------------------------------- | ||
371 | -- Flood protection | ||
372 | -----------------------------------------------------------------------} | ||
373 | |||
374 | defaultFloodFactor :: Int | ||
375 | defaultFloodFactor = 1 | ||
376 | |||
377 | -- | This is a very permissive value, connection setup usually takes | ||
378 | -- around 10-100KB, including both directions. | ||
379 | defaultFloodThreshold :: Int | ||
380 | defaultFloodThreshold = 2 * 1024 * 1024 | ||
381 | |||
382 | -- | A flood detection function. | ||
383 | type Detector stats = Int -- ^ Factor; | ||
384 | -> Int -- ^ Threshold; | ||
385 | -> stats -- ^ Stats to analyse; | ||
386 | -> Bool -- ^ Is this a flooded connection? | ||
387 | |||
388 | defaultDetector :: Detector ConnectionStats | ||
389 | defaultDetector factor threshold s = | ||
390 | transmittedBytes s > threshold && | ||
391 | factor * wastedBytes s > payloadBytes s | ||
392 | |||
393 | -- | Flood detection is used to protect /this/ peer against a /remote/ | ||
394 | -- malicious peer sending meaningless control messages. | ||
395 | data FloodDetector = FloodDetector | ||
396 | { -- | Max ratio of payload bytes to control bytes. | ||
397 | floodFactor :: {-# UNPACK #-} !Int | ||
398 | |||
399 | -- | Max count of bytes connection /setup/ can take including | ||
400 | -- 'Handshake', 'ExtendedHandshake', 'Bitfield', 'Have' and 'Port' | ||
401 | -- messages. This value is used to avoid false positives at the | ||
402 | -- connection initialization. | ||
403 | , floodThreshold :: {-# UNPACK #-} !Int | ||
404 | |||
405 | -- | Flood predicate on the /current/ 'ConnectionStats'. | ||
406 | , floodPredicate :: Detector ConnectionStats | ||
407 | } deriving Show | ||
408 | |||
409 | instance Eq FloodDetector where | ||
410 | a == b = floodFactor a == floodFactor b | ||
411 | && floodThreshold a == floodThreshold b | ||
412 | |||
413 | -- | Flood detector with very permissive options. | ||
414 | instance Default FloodDetector where | ||
415 | def = FloodDetector | ||
416 | { floodFactor = defaultFloodFactor | ||
417 | , floodThreshold = defaultFloodThreshold | ||
418 | , floodPredicate = defaultDetector | ||
419 | } | ||
420 | |||
421 | -- | This peer might drop connection if the detector gives positive answer. | ||
422 | runDetector :: FloodDetector -> ConnectionStats -> Bool | ||
423 | runDetector FloodDetector {..} = floodPredicate floodFactor floodThreshold | ||
424 | |||
425 | {----------------------------------------------------------------------- | ||
426 | -- Options | ||
427 | -----------------------------------------------------------------------} | ||
428 | |||
429 | -- | Various connection settings and limits. | ||
430 | data Options = Options | ||
431 | { -- | How often /this/ peer should send 'KeepAlive' messages. | ||
432 | keepaliveInterval :: {-# UNPACK #-} !Int | ||
433 | |||
434 | -- | /This/ peer will drop connection if a /remote/ peer did not | ||
435 | -- send any message for this period of time. | ||
436 | , keepaliveTimeout :: {-# UNPACK #-} !Int | ||
437 | |||
438 | , requestQueueLength :: {-# UNPACK #-} !Int | ||
439 | |||
440 | -- | Used to protect against flood attacks. | ||
441 | , floodDetector :: FloodDetector | ||
442 | |||
443 | -- | Used to protect against flood attacks in /metadata | ||
444 | -- exchange/. Normally, a requesting peer should request each | ||
445 | -- 'InfoDict' piece only one time, but a malicious peer can | ||
446 | -- saturate wire with 'MetadataRequest' messages thus flooding | ||
447 | -- responding peer. | ||
448 | -- | ||
449 | -- This value set upper bound for number of 'MetadataRequests' | ||
450 | -- for each piece. | ||
451 | -- | ||
452 | , metadataFactor :: {-# UNPACK #-} !Int | ||
453 | |||
454 | -- | Used to protect against out-of-memory attacks: malicious peer | ||
455 | -- can claim that 'totalSize' is, say, 100TB and send some random | ||
456 | -- data instead of infodict pieces. Since requesting peer unable | ||
457 | -- to check not completed infodict via the infohash, the | ||
458 | -- accumulated pieces will allocate the all available memory. | ||
459 | -- | ||
460 | -- This limit set upper bound for 'InfoDict' size. See | ||
461 | -- 'ExtendedMetadata' for more info. | ||
462 | -- | ||
463 | , maxInfoDictSize :: {-# UNPACK #-} !Int | ||
464 | } deriving (Show, Eq) | ||
465 | |||
466 | -- | Permissive default parameters, most likely you don't need to | ||
467 | -- change them. | ||
468 | instance Default Options where | ||
469 | def = Options | ||
470 | { keepaliveInterval = defaultKeepAliveInterval | ||
471 | , keepaliveTimeout = defaultKeepAliveTimeout | ||
472 | , requestQueueLength = defaultRequestQueueLength | ||
473 | , floodDetector = def | ||
474 | , metadataFactor = defaultMetadataFactor | ||
475 | , maxInfoDictSize = defaultMaxInfoDictSize | ||
476 | } | ||
477 | |||
478 | {----------------------------------------------------------------------- | ||
479 | -- Peer status | ||
480 | -----------------------------------------------------------------------} | ||
481 | |||
482 | -- | Connections contain two bits of state on either end: choked or | ||
483 | -- not, and interested or not. | ||
484 | data PeerStatus = PeerStatus | ||
485 | { -- | Choking is a notification that no data will be sent until | ||
486 | -- unchoking happens. | ||
487 | _choking :: !Bool | ||
488 | |||
489 | -- | | ||
490 | , _interested :: !Bool | ||
491 | } deriving (Show, Eq, Ord) | ||
492 | |||
493 | $(makeLenses ''PeerStatus) | ||
494 | |||
495 | instance Pretty PeerStatus where | ||
496 | pPrint PeerStatus {..} = | ||
497 | pPrint (Choking _choking) <+> "and" <+> pPrint (Interested _interested) | ||
498 | |||
499 | -- | Connections start out choked and not interested. | ||
500 | instance Default PeerStatus where | ||
501 | def = PeerStatus True False | ||
502 | |||
503 | instance Monoid PeerStatus where | ||
504 | mempty = def | ||
505 | mappend a b = PeerStatus | ||
506 | { _choking = _choking a && _choking b | ||
507 | , _interested = _interested a || _interested b | ||
508 | } | ||
509 | |||
510 | -- | Can be used to update remote peer status using incoming 'Status' | ||
511 | -- message. | ||
512 | updateStatus :: StatusUpdate -> PeerStatus -> PeerStatus | ||
513 | updateStatus (Choking b) = choking .~ b | ||
514 | updateStatus (Interested b) = interested .~ b | ||
515 | |||
516 | -- | Can be used to generate outcoming messages. | ||
517 | statusUpdates :: PeerStatus -> PeerStatus -> [StatusUpdate] | ||
518 | statusUpdates a b = M.catMaybes $ | ||
519 | [ if _choking a == _choking b then Nothing | ||
520 | else Just $ Choking $ _choking b | ||
521 | , if _interested a == _interested b then Nothing | ||
522 | else Just $ Interested $ _interested b | ||
523 | ] | ||
524 | |||
525 | {----------------------------------------------------------------------- | ||
526 | -- Connection status | ||
527 | -----------------------------------------------------------------------} | ||
528 | |||
529 | -- | Status of the both endpoints. | ||
530 | data ConnectionStatus = ConnectionStatus | ||
531 | { _clientStatus :: !PeerStatus | ||
532 | , _remoteStatus :: !PeerStatus | ||
533 | } deriving (Show, Eq) | ||
534 | |||
535 | $(makeLenses ''ConnectionStatus) | ||
536 | |||
537 | instance Pretty ConnectionStatus where | ||
538 | pPrint ConnectionStatus {..} = | ||
539 | "this " PP.<+> pPrint _clientStatus PP.$$ | ||
540 | "remote" PP.<+> pPrint _remoteStatus | ||
541 | |||
542 | -- | Connections start out choked and not interested. | ||
543 | instance Default ConnectionStatus where | ||
544 | def = ConnectionStatus def def | ||
545 | |||
546 | -- | Can the client transfer to the remote peer? | ||
547 | canUpload :: ConnectionStatus -> Bool | ||
548 | canUpload ConnectionStatus {..} | ||
549 | = _interested _remoteStatus && not (_choking _clientStatus) | ||
550 | |||
551 | -- | Can the client transfer from the remote peer? | ||
552 | canDownload :: ConnectionStatus -> Bool | ||
553 | canDownload ConnectionStatus {..} | ||
554 | = _interested _clientStatus && not (_choking _remoteStatus) | ||
555 | |||
556 | -- | Indicates how many peers are allowed to download from the client | ||
557 | -- by default. | ||
558 | defaultUnchokeSlots :: Int | ||
559 | defaultUnchokeSlots = 4 | ||
560 | |||
561 | -- | | ||
562 | defaultRechokeInterval :: Int | ||
563 | defaultRechokeInterval = 10 * 1000 * 1000 | ||
564 | |||
565 | {----------------------------------------------------------------------- | ||
566 | -- Connection | ||
567 | -----------------------------------------------------------------------} | ||
568 | |||
569 | data ConnectionState = ConnectionState { | ||
570 | -- | If @not (allowed ExtExtended connCaps)@ then this set is always | ||
571 | -- empty. Otherwise it has the BEP10 extension protocol mandated mapping of | ||
572 | -- 'MessageId' to the message type for the remote peer. | ||
573 | -- | ||
574 | -- Note that this value can change in current session if either | ||
575 | -- this or remote peer will initiate rehandshaking. | ||
576 | -- | ||
577 | _connExtCaps :: !ExtendedCaps | ||
578 | |||
579 | -- | Current extended handshake information from the remote peer | ||
580 | , _connRemoteEhs :: !ExtendedHandshake | ||
581 | |||
582 | -- | Various stats about messages sent and received. Stats can be | ||
583 | -- used to protect /this/ peer against flood attacks. | ||
584 | -- | ||
585 | -- Note that this value will change with the next sent or received | ||
586 | -- message. | ||
587 | , _connStats :: !ConnectionStats | ||
588 | |||
589 | , _connStatus :: !ConnectionStatus | ||
590 | |||
591 | -- | Bitfield of remote endpoint. | ||
592 | , _connBitfield :: !Bitfield | ||
593 | } | ||
594 | |||
595 | makeLenses ''ConnectionState | ||
596 | |||
597 | instance Default ConnectionState where | ||
598 | def = ConnectionState | ||
599 | { _connExtCaps = def | ||
600 | , _connRemoteEhs = def | ||
601 | , _connStats = def | ||
602 | , _connStatus = def | ||
603 | , _connBitfield = BF.haveNone 0 | ||
604 | } | ||
605 | |||
606 | -- | Connection keep various info about both peers. | ||
607 | data Connection s = Connection | ||
608 | { connInitiatedBy :: !ChannelSide | ||
609 | |||
610 | , connRemoteAddr :: !(PeerAddr IP) | ||
611 | |||
612 | -- | /Both/ peers handshaked with this protocol string. The only | ||
613 | -- value is \"Bittorrent Protocol\" but this can be changed in | ||
614 | -- future. | ||
615 | , connProtocol :: !ProtocolName | ||
616 | |||
617 | -- | Set of enabled core extensions, i.e. the pre BEP10 extension | ||
618 | -- mechanism. This value is used to check if a message is allowed | ||
619 | -- to be sent or received. | ||
620 | , connCaps :: !Caps | ||
621 | |||
622 | -- | /Both/ peers handshaked with this infohash. A connection can | ||
623 | -- handle only one topic, use 'reconnect' to change the current | ||
624 | -- topic. | ||
625 | , connTopic :: !InfoHash | ||
626 | |||
627 | -- | Typically extracted from handshake. | ||
628 | , connRemotePeerId :: !PeerId | ||
629 | |||
630 | -- | Typically extracted from handshake. | ||
631 | , connThisPeerId :: !PeerId | ||
632 | |||
633 | -- | | ||
634 | , connOptions :: !Options | ||
635 | |||
636 | -- | Mutable connection state, see 'ConnectionState' | ||
637 | , connState :: !(IORef ConnectionState) | ||
638 | |||
639 | -- -- | Max request queue length. | ||
640 | -- , connMaxQueueLen :: !Int | ||
641 | |||
642 | -- | Environment data. | ||
643 | , connSession :: !s | ||
644 | |||
645 | , connChan :: !(Chan Message) | ||
646 | } | ||
647 | |||
648 | instance Pretty (Connection s) where | ||
649 | pPrint Connection {..} = "Connection" | ||
650 | |||
651 | instance ToLogStr (Connection s) where | ||
652 | toLogStr Connection {..} = mconcat | ||
653 | [ toLogStr (show connRemoteAddr) | ||
654 | , toLogStr (show connProtocol) | ||
655 | , toLogStr (show connCaps) | ||
656 | , toLogStr (show connTopic) | ||
657 | , toLogStr (show connRemotePeerId) | ||
658 | , toLogStr (show connThisPeerId) | ||
659 | , toLogStr (show connOptions) | ||
660 | ] | ||
661 | |||
662 | -- TODO check extended messages too | ||
663 | isAllowed :: Connection s -> Message -> Bool | ||
664 | isAllowed Connection {..} msg | ||
665 | | Just ext <- requires msg = ext `allowed` connCaps | ||
666 | | otherwise = True | ||
667 | |||
668 | {----------------------------------------------------------------------- | ||
669 | -- Hanshaking | ||
670 | -----------------------------------------------------------------------} | ||
671 | |||
672 | sendHandshake :: Socket -> Handshake -> IO () | ||
673 | sendHandshake sock hs = sendAll sock (S.encode hs) | ||
674 | |||
675 | recvHandshake :: Socket -> IO Handshake | ||
676 | recvHandshake sock = do | ||
677 | header <- BS.recv sock 1 | ||
678 | unless (BS.length header == 1) $ | ||
679 | throw $ userError "Unable to receive handshake header." | ||
680 | |||
681 | let protocolLen = BS.head header | ||
682 | let restLen = handshakeSize protocolLen - 1 | ||
683 | |||
684 | body <- BS.recv sock restLen | ||
685 | let resp = BS.cons protocolLen body | ||
686 | either (throwIO . userError) return $ S.decode resp | ||
687 | |||
688 | -- | Handshaking with a peer specified by the second argument. | ||
689 | -- | ||
690 | -- It's important to send handshake first because /accepting/ peer | ||
691 | -- do not know handshake topic and will wait until /connecting/ peer | ||
692 | -- will send handshake. | ||
693 | -- | ||
694 | initiateHandshake :: Socket -> Handshake -> IO Handshake | ||
695 | initiateHandshake sock hs = do | ||
696 | sendHandshake sock hs | ||
697 | recvHandshake sock | ||
698 | |||
699 | data HandshakePair = HandshakePair | ||
700 | { handshakeSent :: !Handshake | ||
701 | , handshakeRecv :: !Handshake | ||
702 | } deriving (Show, Eq) | ||
703 | |||
704 | validatePair :: HandshakePair -> PeerAddr IP -> IO () | ||
705 | validatePair (HandshakePair hs hs') addr = Prelude.mapM_ checkProp | ||
706 | [ (def == hsProtocol hs', InvalidProtocol $ hsProtocol hs') | ||
707 | , (hsProtocol hs == hsProtocol hs', UnexpectedProtocol $ hsProtocol hs') | ||
708 | , (hsInfoHash hs == hsInfoHash hs', UnexpectedTopic $ hsInfoHash hs') | ||
709 | , (hsPeerId hs' == fromMaybe (hsPeerId hs') (peerId addr) | ||
710 | , UnexpectedPeerId $ hsPeerId hs') | ||
711 | ] | ||
712 | where | ||
713 | checkProp (t, e) = unless t $ throwIO $ ProtocolError e | ||
714 | |||
715 | -- | Connection state /right/ after handshaking. | ||
716 | establishedStats :: HandshakePair -> ConnectionStats | ||
717 | establishedStats HandshakePair {..} = ConnectionStats | ||
718 | { outcomingFlow = FlowStats 1 $ handshakeStats handshakeSent | ||
719 | , incomingFlow = FlowStats 1 $ handshakeStats handshakeRecv | ||
720 | } | ||
721 | |||
722 | {----------------------------------------------------------------------- | ||
723 | -- Wire | ||
724 | -----------------------------------------------------------------------} | ||
725 | |||
726 | -- | do not expose this so we can change it without breaking api | ||
727 | newtype Connected s a = Connected { runConnected :: (ReaderT (Connection s) IO a) } | ||
728 | deriving (Functor, Applicative, Monad | ||
729 | , MonadIO, MonadReader (Connection s), MonadThrow | ||
730 | ) | ||
731 | |||
732 | instance MonadState ConnectionState (Connected s) where | ||
733 | get = Connected (asks connState) >>= liftIO . readIORef | ||
734 | put x = Connected (asks connState) >>= liftIO . flip writeIORef x | ||
735 | |||
736 | -- | A duplex channel connected to a remote peer which keep tracks | ||
737 | -- connection parameters. | ||
738 | type Wire s a = ConduitM Message Message (Connected s) a | ||
739 | |||
740 | {----------------------------------------------------------------------- | ||
741 | -- Wrapper | ||
742 | -----------------------------------------------------------------------} | ||
743 | |||
744 | putStats :: ChannelSide -> Message -> Connected s () | ||
745 | putStats side msg = connStats %= addStats side (stats msg) | ||
746 | |||
747 | validate :: ChannelSide -> Message -> Connected s () | ||
748 | validate side msg = do | ||
749 | caps <- asks connCaps | ||
750 | case requires msg of | ||
751 | Nothing -> return () | ||
752 | Just ext | ||
753 | | ext `allowed` caps -> return () | ||
754 | | otherwise -> protocolError $ DisallowedMessage side ext | ||
755 | |||
756 | trackFlow :: ChannelSide -> Wire s () | ||
757 | trackFlow side = iterM $ do | ||
758 | validate side | ||
759 | putStats side | ||
760 | |||
761 | {----------------------------------------------------------------------- | ||
762 | -- Setup | ||
763 | -----------------------------------------------------------------------} | ||
764 | |||
765 | -- System.Timeout.timeout multiplier | ||
766 | seconds :: Int | ||
767 | seconds = 1000000 | ||
768 | |||
769 | sinkChan :: MonadIO m => Chan Message -> Sink Message m () | ||
770 | sinkChan chan = await >>= maybe (return ()) (liftIO . writeChan chan) | ||
771 | |||
772 | sourceChan :: MonadIO m => Int -> Chan Message -> Source m Message | ||
773 | sourceChan interval chan = do | ||
774 | mmsg <- liftIO $ timeout (interval * seconds) $ readChan chan | ||
775 | yield $ fromMaybe Msg.KeepAlive mmsg | ||
776 | |||
777 | -- | Normally you should use 'connectWire' or 'acceptWire'. | ||
778 | runWire :: Wire s () -> Socket -> Chan Message -> Connection s -> IO () | ||
779 | runWire action sock chan conn = flip runReaderT conn $ runConnected $ | ||
780 | sourceSocket sock $= | ||
781 | conduitGet S.get $= | ||
782 | trackFlow RemotePeer $= | ||
783 | action $= | ||
784 | trackFlow ThisPeer C.$$ | ||
785 | sinkChan chan | ||
786 | |||
787 | -- | This function will block until a peer send new message. You can | ||
788 | -- also use 'await'. | ||
789 | recvMessage :: Wire s Message | ||
790 | recvMessage = await >>= maybe (monadThrow PeerDisconnected) return | ||
791 | |||
792 | -- | You can also use 'yield'. | ||
793 | sendMessage :: PeerMessage msg => msg -> Wire s () | ||
794 | sendMessage msg = do | ||
795 | ecaps <- use connExtCaps | ||
796 | yield $ envelop ecaps msg | ||
797 | |||
798 | getMaxQueueLength :: Connected s Int | ||
799 | getMaxQueueLength = do | ||
800 | advertisedLen <- ehsQueueLength <$> use connRemoteEhs | ||
801 | defaultLen <- asks (requestQueueLength . connOptions) | ||
802 | return $ fromMaybe defaultLen advertisedLen | ||
803 | |||
804 | -- | Filter pending messages from send buffer. | ||
805 | filterQueue :: (Message -> Bool) -> Wire s () | ||
806 | filterQueue p = lift $ do | ||
807 | chan <- asks connChan | ||
808 | liftIO $ getChanContents chan >>= writeList2Chan chan . L.filter p | ||
809 | |||
810 | -- | Forcefully terminate wire session and close socket. | ||
811 | disconnectPeer :: Wire s a | ||
812 | disconnectPeer = monadThrow DisconnectPeer | ||
813 | |||
814 | extendedHandshake :: ExtendedCaps -> Wire s () | ||
815 | extendedHandshake caps = do | ||
816 | -- TODO add other params to the handshake | ||
817 | sendMessage $ nullExtendedHandshake caps | ||
818 | msg <- recvMessage | ||
819 | case msg of | ||
820 | Extended (EHandshake remoteEhs@(ExtendedHandshake {..})) -> do | ||
821 | connExtCaps .= (ehsCaps <> caps) | ||
822 | connRemoteEhs .= remoteEhs | ||
823 | _ -> protocolError HandshakeRefused | ||
824 | |||
825 | rehandshake :: ExtendedCaps -> Wire s () | ||
826 | rehandshake caps = error "rehandshake" | ||
827 | |||
828 | reconnect :: Wire s () | ||
829 | reconnect = error "reconnect" | ||
830 | |||
831 | data ConnectionId = ConnectionId | ||
832 | { topic :: !InfoHash | ||
833 | , remoteAddr :: !(PeerAddr IP) | ||
834 | , thisAddr :: !(PeerAddr (Maybe IP)) -- ^ foreign address of this node. | ||
835 | } | ||
836 | |||
837 | -- | /Preffered/ settings of wire. To get the real use 'ask'. | ||
838 | data ConnectionPrefs = ConnectionPrefs | ||
839 | { prefOptions :: !Options | ||
840 | , prefProtocol :: !ProtocolName | ||
841 | , prefCaps :: !Caps | ||
842 | , prefExtCaps :: !ExtendedCaps | ||
843 | } deriving (Show, Eq) | ||
844 | |||
845 | instance Default ConnectionPrefs where | ||
846 | def = ConnectionPrefs | ||
847 | { prefOptions = def | ||
848 | , prefProtocol = def | ||
849 | , prefCaps = def | ||
850 | , prefExtCaps = def | ||
851 | } | ||
852 | |||
853 | normalize :: ConnectionPrefs -> ConnectionPrefs | ||
854 | normalize = error "normalize" | ||
855 | |||
856 | -- | Bridge between 'Connection' and 'Network.BitTorrent.Exchange.Session'. | ||
857 | data SessionLink s = SessionLink | ||
858 | { linkTopic :: !(InfoHash) | ||
859 | , linkPeerId :: !(PeerId) | ||
860 | , linkMetadataSize :: !(Maybe Int) | ||
861 | , linkOutputChan :: !(Maybe (Chan Message)) | ||
862 | , linkSession :: !(s) | ||
863 | } | ||
864 | |||
865 | data ConnectionConfig s = ConnectionConfig | ||
866 | { cfgPrefs :: !(ConnectionPrefs) | ||
867 | , cfgSession :: !(SessionLink s) | ||
868 | , cfgWire :: !(Wire s ()) | ||
869 | } | ||
870 | |||
871 | configHandshake :: ConnectionConfig s -> Handshake | ||
872 | configHandshake ConnectionConfig {..} = Handshake | ||
873 | { hsProtocol = prefProtocol cfgPrefs | ||
874 | , hsReserved = prefCaps cfgPrefs | ||
875 | , hsInfoHash = linkTopic cfgSession | ||
876 | , hsPeerId = linkPeerId cfgSession | ||
877 | } | ||
878 | |||
879 | {----------------------------------------------------------------------- | ||
880 | -- Pending connections | ||
881 | -----------------------------------------------------------------------} | ||
882 | |||
883 | -- | Connection in half opened state. A normal usage scenario: | ||
884 | -- | ||
885 | -- * Opened using 'newPendingConnection', usually in the listener | ||
886 | -- loop; | ||
887 | -- | ||
888 | -- * Closed using 'closePending' if 'pendingPeer' is banned, | ||
889 | -- 'pendingCaps' is prohibited or pendingTopic is unknown; | ||
890 | -- | ||
891 | -- * Accepted using 'acceptWire' otherwise. | ||
892 | -- | ||
893 | data PendingConnection = PendingConnection | ||
894 | { pendingSock :: Socket | ||
895 | , pendingPeer :: PeerAddr IP -- ^ 'peerId' is always non empty; | ||
896 | , pendingCaps :: Caps -- ^ advertised by the peer; | ||
897 | , pendingTopic :: InfoHash -- ^ possible non-existent topic. | ||
898 | } | ||
899 | |||
900 | -- | Reconstruct handshake sent by the remote peer. | ||
901 | pendingHandshake :: PendingConnection -> Handshake | ||
902 | pendingHandshake PendingConnection {..} = Handshake | ||
903 | { hsProtocol = def | ||
904 | , hsReserved = pendingCaps | ||
905 | , hsInfoHash = pendingTopic | ||
906 | , hsPeerId = fromMaybe (error "pendingHandshake: impossible") | ||
907 | (peerId pendingPeer) | ||
908 | } | ||
909 | |||
910 | -- | | ||
911 | -- | ||
912 | -- This function can throw 'WireFailure' exception. | ||
913 | -- | ||
914 | newPendingConnection :: Socket -> PeerAddr IP -> IO PendingConnection | ||
915 | newPendingConnection sock addr = do | ||
916 | Handshake {..} <- recvHandshake sock | ||
917 | unless (hsProtocol == def) $ do | ||
918 | throwIO $ ProtocolError $ InvalidProtocol hsProtocol | ||
919 | return PendingConnection | ||
920 | { pendingSock = sock | ||
921 | , pendingPeer = addr { peerId = Just hsPeerId } | ||
922 | , pendingCaps = hsReserved | ||
923 | , pendingTopic = hsInfoHash | ||
924 | } | ||
925 | |||
926 | -- | Release all resources associated with the given connection. Note | ||
927 | -- that you /must not/ 'closePending' if you 'acceptWire'. | ||
928 | closePending :: PendingConnection -> IO () | ||
929 | closePending PendingConnection {..} = do | ||
930 | close pendingSock | ||
931 | |||
932 | {----------------------------------------------------------------------- | ||
933 | -- Connection setup | ||
934 | -----------------------------------------------------------------------} | ||
935 | |||
936 | chanToSock :: Int -> Chan Message -> Socket -> IO () | ||
937 | chanToSock ka chan sock = | ||
938 | sourceChan ka chan $= conduitPut S.put C.$$ sinkSocket sock | ||
939 | |||
940 | afterHandshaking :: ChannelSide -> PeerAddr IP -> Socket -> HandshakePair | ||
941 | -> ConnectionConfig s -> IO () | ||
942 | afterHandshaking initiator addr sock | ||
943 | hpair @ (HandshakePair hs hs') | ||
944 | (ConnectionConfig | ||
945 | { cfgPrefs = ConnectionPrefs {..} | ||
946 | , cfgSession = SessionLink {..} | ||
947 | , cfgWire = wire | ||
948 | }) = do | ||
949 | let caps = hsReserved hs <> hsReserved hs' | ||
950 | cstate <- newIORef def { _connStats = establishedStats hpair } | ||
951 | chan <- maybe newChan return linkOutputChan | ||
952 | let conn = Connection { | ||
953 | connInitiatedBy = initiator | ||
954 | , connRemoteAddr = addr | ||
955 | , connProtocol = hsProtocol hs | ||
956 | , connCaps = caps | ||
957 | , connTopic = hsInfoHash hs | ||
958 | , connRemotePeerId = hsPeerId hs' | ||
959 | , connThisPeerId = hsPeerId hs | ||
960 | , connOptions = def | ||
961 | , connState = cstate | ||
962 | , connSession = linkSession | ||
963 | , connChan = chan | ||
964 | } | ||
965 | |||
966 | -- TODO make KA interval configurable | ||
967 | let kaInterval = defaultKeepAliveInterval | ||
968 | wire' = if ExtExtended `allowed` caps | ||
969 | then extendedHandshake prefExtCaps >> wire | ||
970 | else wire | ||
971 | |||
972 | bracket (forkIO (chanToSock kaInterval chan sock)) | ||
973 | (killThread) | ||
974 | (\ _ -> runWire wire' sock chan conn) | ||
975 | |||
976 | -- | Initiate 'Wire' connection and handshake with a peer. This function will | ||
977 | -- also do the BEP10 extension protocol handshake if 'ExtExtended' is enabled on | ||
978 | -- both sides. | ||
979 | -- | ||
980 | -- This function can throw 'WireFailure' exception. | ||
981 | -- | ||
982 | connectWire :: PeerAddr IP -> ConnectionConfig s -> IO () | ||
983 | connectWire addr cfg = do | ||
984 | let catchRefusal m = try m >>= either (throwIO . ConnectionRefused) return | ||
985 | bracket (catchRefusal (peerSocket Stream addr)) close $ \ sock -> do | ||
986 | let hs = configHandshake cfg | ||
987 | hs' <- initiateHandshake sock hs | ||
988 | let hpair = HandshakePair hs hs' | ||
989 | validatePair hpair addr | ||
990 | afterHandshaking ThisPeer addr sock hpair cfg | ||
991 | |||
992 | -- | Accept 'Wire' connection using already 'Network.Socket.accept'ed | ||
993 | -- socket. For peer listener loop the 'acceptSafe' should be | ||
994 | -- prefered against 'accept'. The socket will be closed at exit. | ||
995 | -- | ||
996 | -- This function can throw 'WireFailure' exception. | ||
997 | -- | ||
998 | acceptWire :: PendingConnection -> ConnectionConfig s -> IO () | ||
999 | acceptWire pc @ PendingConnection {..} cfg = do | ||
1000 | bracket (return pendingSock) close $ \ _ -> do | ||
1001 | unless (linkTopic (cfgSession cfg) == pendingTopic) $ do | ||
1002 | throwIO (ProtocolError (UnexpectedTopic pendingTopic)) | ||
1003 | |||
1004 | let hs = configHandshake cfg | ||
1005 | sendHandshake pendingSock hs | ||
1006 | let hpair = HandshakePair hs (pendingHandshake pc) | ||
1007 | |||
1008 | afterHandshaking RemotePeer pendingPeer pendingSock hpair cfg | ||
1009 | |||
1010 | -- | Used when size of bitfield becomes known. | ||
1011 | resizeBitfield :: Int -> Connected s () | ||
1012 | resizeBitfield n = connBitfield %= adjustSize n | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange/Download.hs b/bittorrent/src/Network/BitTorrent/Exchange/Download.hs new file mode 100644 index 00000000..981db2fb --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange/Download.hs | |||
@@ -0,0 +1,296 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- | ||
9 | -- | ||
10 | {-# LANGUAGE FlexibleContexts #-} | ||
11 | {-# LANGUAGE FlexibleInstances #-} | ||
12 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
13 | {-# LANGUAGE FunctionalDependencies #-} | ||
14 | {-# LANGUAGE TemplateHaskell #-} | ||
15 | module Network.BitTorrent.Exchange.Download | ||
16 | ( -- * Downloading | ||
17 | Download (..) | ||
18 | , Updates | ||
19 | , runDownloadUpdates | ||
20 | |||
21 | -- ** Metadata | ||
22 | -- $metadata-download | ||
23 | , MetadataDownload | ||
24 | , metadataDownload | ||
25 | |||
26 | -- ** Content | ||
27 | -- $content-download | ||
28 | , ContentDownload | ||
29 | , contentDownload | ||
30 | ) where | ||
31 | |||
32 | import Control.Applicative | ||
33 | import Control.Concurrent | ||
34 | import Control.Lens | ||
35 | import Control.Monad.State | ||
36 | import Data.BEncode as BE | ||
37 | import Data.ByteString as BS | ||
38 | import Data.ByteString.Lazy as BL | ||
39 | import Data.Default | ||
40 | import Data.List as L | ||
41 | import Data.Maybe | ||
42 | import Data.Map as M | ||
43 | import Data.Tuple | ||
44 | |||
45 | import Data.Torrent as Torrent | ||
46 | import Network.Address | ||
47 | import Network.BitTorrent.Exchange.Bitfield as BF | ||
48 | import Network.BitTorrent.Exchange.Block as Block | ||
49 | import Network.BitTorrent.Exchange.Message as Msg | ||
50 | import System.Torrent.Storage (Storage, writePiece) | ||
51 | |||
52 | |||
53 | {----------------------------------------------------------------------- | ||
54 | -- Class | ||
55 | -----------------------------------------------------------------------} | ||
56 | |||
57 | type Updates s a = StateT s IO a | ||
58 | |||
59 | runDownloadUpdates :: MVar s -> Updates s a -> IO a | ||
60 | runDownloadUpdates var m = modifyMVar var (fmap swap . runStateT m) | ||
61 | |||
62 | class Download s chunk | s -> chunk where | ||
63 | scheduleBlocks :: Int -> PeerAddr IP -> Bitfield -> Updates s [BlockIx] | ||
64 | |||
65 | -- | | ||
66 | scheduleBlock :: PeerAddr IP -> Bitfield -> Updates s (Maybe BlockIx) | ||
67 | scheduleBlock addr bf = listToMaybe <$> scheduleBlocks 1 addr bf | ||
68 | |||
69 | -- | Get number of sent requests to this peer. | ||
70 | getRequestQueueLength :: PeerAddr IP -> Updates s Int | ||
71 | |||
72 | -- | Remove all pending block requests to the remote peer. May be used | ||
73 | -- when: | ||
74 | -- | ||
75 | -- * a peer closes connection; | ||
76 | -- | ||
77 | -- * remote peer choked this peer; | ||
78 | -- | ||
79 | -- * timeout expired. | ||
80 | -- | ||
81 | resetPending :: PeerAddr IP -> Updates s () | ||
82 | |||
83 | -- | MAY write to storage, if a new piece have been completed. | ||
84 | -- | ||
85 | -- You should check if a returned by peer block is actually have | ||
86 | -- been requested and in-flight. This is needed to avoid "I send | ||
87 | -- random corrupted block" attacks. | ||
88 | pushBlock :: PeerAddr IP -> chunk -> Updates s (Maybe Bool) | ||
89 | |||
90 | {----------------------------------------------------------------------- | ||
91 | -- Metadata download | ||
92 | -----------------------------------------------------------------------} | ||
93 | -- $metadata-download | ||
94 | -- TODO | ||
95 | |||
96 | data MetadataDownload = MetadataDownload | ||
97 | { _pendingPieces :: [(PeerAddr IP, PieceIx)] | ||
98 | , _bucket :: Bucket | ||
99 | , _topic :: InfoHash | ||
100 | } | ||
101 | |||
102 | makeLenses ''MetadataDownload | ||
103 | |||
104 | -- | Create a new scheduler for infodict of the given size. | ||
105 | metadataDownload :: Int -> InfoHash -> MetadataDownload | ||
106 | metadataDownload ps = MetadataDownload [] (Block.empty ps) | ||
107 | |||
108 | instance Default MetadataDownload where | ||
109 | def = error "instance Default MetadataDownload" | ||
110 | |||
111 | --cancelPending :: PieceIx -> Updates () | ||
112 | cancelPending pix = pendingPieces %= L.filter ((pix ==) . snd) | ||
113 | |||
114 | instance Download MetadataDownload (Piece BS.ByteString) where | ||
115 | scheduleBlock addr bf = do | ||
116 | bkt <- use bucket | ||
117 | case spans metadataPieceSize bkt of | ||
118 | [] -> return Nothing | ||
119 | ((off, _ ) : _) -> do | ||
120 | let pix = off `div` metadataPieceSize | ||
121 | pendingPieces %= ((addr, pix) :) | ||
122 | return (Just (BlockIx pix 0 metadataPieceSize)) | ||
123 | |||
124 | resetPending addr = pendingPieces %= L.filter ((addr ==) . fst) | ||
125 | |||
126 | pushBlock addr Torrent.Piece {..} = do | ||
127 | p <- use pendingPieces | ||
128 | when ((addr, pieceIndex) `L.notElem` p) $ | ||
129 | error "not requested" | ||
130 | cancelPending pieceIndex | ||
131 | |||
132 | bucket %= Block.insert (metadataPieceSize * pieceIndex) pieceData | ||
133 | b <- use bucket | ||
134 | case toPiece b of | ||
135 | Nothing -> return Nothing | ||
136 | Just chunks -> do | ||
137 | t <- use topic | ||
138 | case parseInfoDict (BL.toStrict chunks) t of | ||
139 | Right x -> do | ||
140 | pendingPieces .= [] | ||
141 | return undefined -- (Just x) | ||
142 | Left e -> do | ||
143 | pendingPieces .= [] | ||
144 | bucket .= Block.empty (Block.size b) | ||
145 | return undefined -- Nothing | ||
146 | where | ||
147 | -- todo use incremental parsing to avoid BS.concat call | ||
148 | parseInfoDict :: BS.ByteString -> InfoHash -> Result InfoDict | ||
149 | parseInfoDict chunk topic = | ||
150 | case BE.decode chunk of | ||
151 | Right (infodict @ InfoDict {..}) | ||
152 | | topic == idInfoHash -> return infodict | ||
153 | | otherwise -> Left "broken infodict" | ||
154 | Left err -> Left $ "unable to parse infodict " ++ err | ||
155 | |||
156 | {----------------------------------------------------------------------- | ||
157 | -- Content download | ||
158 | -----------------------------------------------------------------------} | ||
159 | -- $content-download | ||
160 | -- | ||
161 | -- A block can have one of the following status: | ||
162 | -- | ||
163 | -- 1) /not allowed/: Piece is not in download set. | ||
164 | -- | ||
165 | -- 2) /waiting/: (allowed?) Block have been allowed to download, | ||
166 | -- but /this/ peer did not send any 'Request' message for this | ||
167 | -- block. To allow some piece use | ||
168 | -- 'Network.BitTorrent.Exchange.Selector' and then 'allowedSet' | ||
169 | -- and 'allowPiece'. | ||
170 | -- | ||
171 | -- 3) /inflight/: (pending?) Block have been requested but | ||
172 | -- /remote/ peer did not send any 'Piece' message for this block. | ||
173 | -- Related functions 'markInflight' | ||
174 | -- | ||
175 | -- 4) /pending/: (stalled?) Block have have been downloaded | ||
176 | -- Related functions 'insertBlock'. | ||
177 | -- | ||
178 | -- Piece status: | ||
179 | -- | ||
180 | -- 1) /assembled/: (downloaded?) All blocks in piece have been | ||
181 | -- downloaded but the piece did not verified yet. | ||
182 | -- | ||
183 | -- * Valid: go to completed; | ||
184 | -- | ||
185 | -- * Invalid: go to waiting. | ||
186 | -- | ||
187 | -- 2) /corrupted/: | ||
188 | -- | ||
189 | -- 3) /downloaded/: (verified?) A piece have been successfully | ||
190 | -- verified via the hash. Usually the piece should be stored to | ||
191 | -- the 'System.Torrent.Storage' and /this/ peer should send 'Have' | ||
192 | -- messages to the /remote/ peers. | ||
193 | -- | ||
194 | |||
195 | data PieceEntry = PieceEntry | ||
196 | { pending :: [(PeerAddr IP, BlockIx)] | ||
197 | , stalled :: Bucket | ||
198 | } | ||
199 | |||
200 | pieceEntry :: PieceSize -> PieceEntry | ||
201 | pieceEntry s = PieceEntry [] (Block.empty s) | ||
202 | |||
203 | isEmpty :: PieceEntry -> Bool | ||
204 | isEmpty PieceEntry {..} = L.null pending && Block.null stalled | ||
205 | |||
206 | _holes :: PieceIx -> PieceEntry -> [BlockIx] | ||
207 | _holes pix PieceEntry {..} = fmap mkBlockIx (spans defaultTransferSize stalled) | ||
208 | where | ||
209 | mkBlockIx (off, sz) = BlockIx pix off sz | ||
210 | |||
211 | data ContentDownload = ContentDownload | ||
212 | { inprogress :: !(Map PieceIx PieceEntry) | ||
213 | , bitfield :: !Bitfield | ||
214 | , pieceSize :: !PieceSize | ||
215 | , contentStorage :: Storage | ||
216 | } | ||
217 | |||
218 | contentDownload :: Bitfield -> PieceSize -> Storage -> ContentDownload | ||
219 | contentDownload = ContentDownload M.empty | ||
220 | |||
221 | --modifyEntry :: PieceIx -> (PieceEntry -> PieceEntry) -> DownloadUpdates () | ||
222 | modifyEntry pix f = modify $ \ s @ ContentDownload {..} -> s | ||
223 | { inprogress = alter (g pieceSize) pix inprogress } | ||
224 | where | ||
225 | g s = h . f . fromMaybe (pieceEntry s) | ||
226 | h e | ||
227 | | isEmpty e = Nothing | ||
228 | | otherwise = Just e | ||
229 | |||
230 | instance Download ContentDownload (Block BL.ByteString) where | ||
231 | scheduleBlocks n addr maskBF = do | ||
232 | ContentDownload {..} <- get | ||
233 | let wantPieces = maskBF `BF.difference` bitfield | ||
234 | let wantBlocks = L.concat $ M.elems $ M.mapWithKey _holes $ | ||
235 | M.filterWithKey (\ pix _ -> pix `BF.member` wantPieces) | ||
236 | inprogress | ||
237 | |||
238 | bixs <- if L.null wantBlocks | ||
239 | then do | ||
240 | mpix <- choosePiece wantPieces | ||
241 | case mpix of -- TODO return 'n' blocks | ||
242 | Nothing -> return [] | ||
243 | Just pix -> return [leadingBlock pix defaultTransferSize] | ||
244 | else chooseBlocks wantBlocks n | ||
245 | |||
246 | forM_ bixs $ \ bix -> do | ||
247 | modifyEntry (ixPiece bix) $ \ e @ PieceEntry {..} -> e | ||
248 | { pending = (addr, bix) : pending } | ||
249 | |||
250 | return bixs | ||
251 | where | ||
252 | -- TODO choose block nearest to pending or stalled sets to reduce disk | ||
253 | -- seeks on remote machines | ||
254 | --chooseBlocks :: [BlockIx] -> Int -> DownloadUpdates [BlockIx] | ||
255 | chooseBlocks xs n = return (L.take n xs) | ||
256 | |||
257 | -- TODO use selection strategies from Exchange.Selector | ||
258 | --choosePiece :: Bitfield -> DownloadUpdates (Maybe PieceIx) | ||
259 | choosePiece bf | ||
260 | | BF.null bf = return $ Nothing | ||
261 | | otherwise = return $ Just $ BF.findMin bf | ||
262 | |||
263 | getRequestQueueLength addr = do | ||
264 | m <- gets (M.map (L.filter ((==) addr . fst) . pending) . inprogress) | ||
265 | return $ L.sum $ L.map L.length $ M.elems m | ||
266 | |||
267 | resetPending addr = modify $ \ s -> s { inprogress = reset (inprogress s) } | ||
268 | where | ||
269 | reset = fmap $ \ e -> e | ||
270 | { pending = L.filter (not . (==) addr . fst) (pending e) } | ||
271 | |||
272 | pushBlock addr blk @ Block {..} = do | ||
273 | mpe <- gets (M.lookup blkPiece . inprogress) | ||
274 | case mpe of | ||
275 | Nothing -> return Nothing | ||
276 | Just (pe @ PieceEntry {..}) | ||
277 | | blockIx blk `L.notElem` fmap snd pending -> return Nothing | ||
278 | | otherwise -> do | ||
279 | let bkt' = Block.insertLazy blkOffset blkData stalled | ||
280 | case toPiece bkt' of | ||
281 | Nothing -> do | ||
282 | modifyEntry blkPiece $ \ e @ PieceEntry {..} -> e | ||
283 | { pending = L.filter ((==) (blockIx blk) . snd) pending | ||
284 | , stalled = bkt' | ||
285 | } | ||
286 | return (Just False) | ||
287 | |||
288 | Just pieceData -> do | ||
289 | -- TODO verify | ||
290 | storage <- gets contentStorage | ||
291 | liftIO $ writePiece (Torrent.Piece blkPiece pieceData) storage | ||
292 | modify $ \ s @ ContentDownload {..} -> s | ||
293 | { inprogress = M.delete blkPiece inprogress | ||
294 | , bitfield = BF.insert blkPiece bitfield | ||
295 | } | ||
296 | return (Just True) | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange/Manager.hs b/bittorrent/src/Network/BitTorrent/Exchange/Manager.hs new file mode 100644 index 00000000..30a6a607 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange/Manager.hs | |||
@@ -0,0 +1,62 @@ | |||
1 | module Network.BitTorrent.Exchange.Manager | ||
2 | ( Options (..) | ||
3 | , Manager | ||
4 | , Handler | ||
5 | , newManager | ||
6 | , closeManager | ||
7 | ) where | ||
8 | |||
9 | import Control.Concurrent | ||
10 | import Control.Exception hiding (Handler) | ||
11 | import Control.Monad | ||
12 | import Data.Default | ||
13 | import Network.Socket | ||
14 | |||
15 | import Data.Torrent | ||
16 | import Network.Address | ||
17 | import Network.BitTorrent.Exchange.Connection hiding (Options) | ||
18 | import Network.BitTorrent.Exchange.Session | ||
19 | |||
20 | |||
21 | data Options = Options | ||
22 | { optBacklog :: Int | ||
23 | , optPeerAddr :: PeerAddr IP | ||
24 | } deriving (Show, Eq) | ||
25 | |||
26 | instance Default Options where | ||
27 | def = Options | ||
28 | { optBacklog = maxListenQueue | ||
29 | , optPeerAddr = def | ||
30 | } | ||
31 | |||
32 | data Manager = Manager | ||
33 | { listener :: !ThreadId | ||
34 | } | ||
35 | |||
36 | type Handler = InfoHash -> IO Session | ||
37 | |||
38 | handleNewConn :: Socket -> PeerAddr IP -> Handler -> IO () | ||
39 | handleNewConn sock addr handler = do | ||
40 | conn <- newPendingConnection sock addr | ||
41 | ses <- handler (pendingTopic conn) `onException` closePending conn | ||
42 | establish conn ses | ||
43 | |||
44 | listenIncoming :: Options -> Handler -> IO () | ||
45 | listenIncoming Options {..} handler = do | ||
46 | bracket (socket AF_INET Stream defaultProtocol) close $ \ sock -> do | ||
47 | bind sock (toSockAddr optPeerAddr) | ||
48 | listen sock optBacklog | ||
49 | forever $ do | ||
50 | (conn, sockAddr) <- accept sock | ||
51 | case fromSockAddr sockAddr of | ||
52 | Nothing -> return () | ||
53 | Just addr -> void $ forkIO $ handleNewConn sock addr handler | ||
54 | |||
55 | newManager :: Options -> Handler -> IO Manager | ||
56 | newManager opts handler = do | ||
57 | tid <- forkIO $ listenIncoming opts handler | ||
58 | return (Manager tid) | ||
59 | |||
60 | closeManager :: Manager -> IO () | ||
61 | closeManager Manager {..} = do | ||
62 | killThread listener \ No newline at end of file | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange/Message.hs b/bittorrent/src/Network/BitTorrent/Exchange/Message.hs new file mode 100644 index 00000000..2c6770f7 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange/Message.hs | |||
@@ -0,0 +1,1232 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Normally peer to peer communication consisting of the following | ||
9 | -- steps: | ||
10 | -- | ||
11 | -- * In order to establish the connection between peers we should | ||
12 | -- send 'Handshake' message. The 'Handshake' is a required message | ||
13 | -- and must be the first message transmitted by the peer to the | ||
14 | -- another peer. Another peer should reply with a handshake as well. | ||
15 | -- | ||
16 | -- * Next peer might sent bitfield message, but might not. In the | ||
17 | -- former case we should update bitfield peer have. Again, if we | ||
18 | -- have some pieces we should send bitfield. Normally bitfield | ||
19 | -- message should sent after the handshake message. | ||
20 | -- | ||
21 | -- * Regular exchange messages. TODO docs | ||
22 | -- | ||
23 | -- For more high level API see "Network.BitTorrent.Exchange" module. | ||
24 | -- | ||
25 | -- For more infomation see: | ||
26 | -- <https://wiki.theory.org/BitTorrentSpecification#Peer_wire_protocol_.28TCP.29> | ||
27 | -- | ||
28 | {-# LANGUAGE ViewPatterns #-} | ||
29 | {-# LANGUAGE FlexibleInstances #-} | ||
30 | {-# LANGUAGE FlexibleContexts #-} | ||
31 | {-# LANGUAGE TypeFamilies #-} | ||
32 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
33 | {-# LANGUAGE DeriveDataTypeable #-} | ||
34 | {-# LANGUAGE TemplateHaskell #-} | ||
35 | {-# OPTIONS -fno-warn-orphans #-} | ||
36 | module Network.BitTorrent.Exchange.Message | ||
37 | ( -- * Capabilities | ||
38 | Capabilities (..) | ||
39 | , Extension (..) | ||
40 | , Caps | ||
41 | |||
42 | -- * Handshake | ||
43 | , ProtocolName | ||
44 | , Handshake(..) | ||
45 | , defaultHandshake | ||
46 | , handshakeSize | ||
47 | , handshakeMaxSize | ||
48 | , handshakeStats | ||
49 | |||
50 | -- * Stats | ||
51 | , ByteCount | ||
52 | , ByteStats (..) | ||
53 | , byteLength | ||
54 | |||
55 | -- * Messages | ||
56 | , Message (..) | ||
57 | , defaultKeepAliveTimeout | ||
58 | , defaultKeepAliveInterval | ||
59 | , PeerMessage (..) | ||
60 | |||
61 | -- ** Core messages | ||
62 | , StatusUpdate (..) | ||
63 | , Available (..) | ||
64 | , Transfer (..) | ||
65 | , defaultRequestQueueLength | ||
66 | |||
67 | -- ** Fast extension | ||
68 | , FastMessage (..) | ||
69 | |||
70 | -- ** Extension protocol | ||
71 | , ExtendedMessage (..) | ||
72 | |||
73 | -- *** Capabilities | ||
74 | , ExtendedExtension (..) | ||
75 | , ExtendedCaps (..) | ||
76 | |||
77 | -- *** Handshake | ||
78 | , ExtendedHandshake (..) | ||
79 | , defaultQueueLength | ||
80 | , nullExtendedHandshake | ||
81 | |||
82 | -- *** Metadata | ||
83 | , ExtendedMetadata (..) | ||
84 | , metadataPieceSize | ||
85 | , defaultMetadataFactor | ||
86 | , defaultMaxInfoDictSize | ||
87 | , isLastPiece | ||
88 | , isValidPiece | ||
89 | ) where | ||
90 | |||
91 | import Control.Applicative | ||
92 | import Control.Arrow ((&&&), (***)) | ||
93 | import Control.Monad (when) | ||
94 | import Data.Attoparsec.ByteString.Char8 as BS | ||
95 | import Data.BEncode as BE | ||
96 | import Data.BEncode.BDict as BE | ||
97 | import Data.BEncode.Internal as BE (ppBEncode, parser) | ||
98 | import Data.BEncode.Types (BDict) | ||
99 | import Data.Bits | ||
100 | import Data.ByteString as BS | ||
101 | import Data.ByteString.Char8 as BC | ||
102 | import Data.ByteString.Lazy as BL | ||
103 | import Data.Default | ||
104 | import Data.List as L | ||
105 | import Data.Map.Strict as M | ||
106 | import Data.Maybe | ||
107 | import Data.Monoid | ||
108 | import Data.Ord | ||
109 | import Data.Serialize as S | ||
110 | import Data.String | ||
111 | import Data.Text as T | ||
112 | import Data.Typeable | ||
113 | import Data.Word | ||
114 | import Data.IP | ||
115 | import Network | ||
116 | import Network.Socket hiding (KeepAlive) | ||
117 | import Text.PrettyPrint as PP hiding ((<>)) | ||
118 | import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) | ||
119 | |||
120 | import Data.Torrent hiding (Piece (..)) | ||
121 | import qualified Data.Torrent as P (Piece (..)) | ||
122 | import Network.Address | ||
123 | import Network.BitTorrent.Exchange.Bitfield | ||
124 | import Network.BitTorrent.Exchange.Block | ||
125 | |||
126 | {----------------------------------------------------------------------- | ||
127 | -- Capabilities | ||
128 | -----------------------------------------------------------------------} | ||
129 | |||
130 | -- | | ||
131 | class Capabilities caps where | ||
132 | type Ext caps :: * | ||
133 | |||
134 | -- | Pack extensions to caps. | ||
135 | toCaps :: [Ext caps] -> caps | ||
136 | |||
137 | -- | Unpack extensions from caps. | ||
138 | fromCaps :: caps -> [Ext caps] | ||
139 | |||
140 | -- | Check if an extension is a member of the specified set. | ||
141 | allowed :: Ext caps -> caps -> Bool | ||
142 | |||
143 | ppCaps :: Capabilities caps => Pretty (Ext caps) => caps -> Doc | ||
144 | ppCaps = hcat . punctuate ", " . L.map pPrint . fromCaps | ||
145 | |||
146 | {----------------------------------------------------------------------- | ||
147 | -- Extensions | ||
148 | -----------------------------------------------------------------------} | ||
149 | |||
150 | -- | Enumeration of message extension protocols. | ||
151 | -- | ||
152 | -- For more info see: <http://www.bittorrent.org/beps/bep_0004.html> | ||
153 | -- | ||
154 | data Extension | ||
155 | = ExtDHT -- ^ BEP 5: allow to send PORT messages. | ||
156 | | ExtFast -- ^ BEP 6: allow to send FAST messages. | ||
157 | | ExtExtended -- ^ BEP 10: allow to send the extension protocol messages. | ||
158 | deriving (Show, Eq, Ord, Enum, Bounded) | ||
159 | |||
160 | -- | Full extension names, suitable for logging. | ||
161 | instance Pretty Extension where | ||
162 | pPrint ExtDHT = "Distributed Hash Table Protocol" | ||
163 | pPrint ExtFast = "Fast Extension" | ||
164 | pPrint ExtExtended = "Extension Protocol" | ||
165 | |||
166 | -- | Extension bitmask as specified by BEP 4. | ||
167 | extMask :: Extension -> Word64 | ||
168 | extMask ExtDHT = 0x01 | ||
169 | extMask ExtFast = 0x04 | ||
170 | extMask ExtExtended = 0x100000 | ||
171 | |||
172 | {----------------------------------------------------------------------- | ||
173 | -- Capabilities | ||
174 | -----------------------------------------------------------------------} | ||
175 | |||
176 | -- | Capabilities is a set of 'Extension's usually sent in 'Handshake' | ||
177 | -- messages. | ||
178 | newtype Caps = Caps Word64 | ||
179 | deriving (Show, Eq) | ||
180 | |||
181 | -- | Render set of extensions as comma separated list. | ||
182 | instance Pretty Caps where | ||
183 | pPrint = ppCaps | ||
184 | {-# INLINE pPrint #-} | ||
185 | |||
186 | -- | The empty set. | ||
187 | instance Default Caps where | ||
188 | def = Caps 0 | ||
189 | {-# INLINE def #-} | ||
190 | |||
191 | -- | Monoid under intersection. 'mempty' includes all known extensions. | ||
192 | instance Monoid Caps where | ||
193 | mempty = toCaps [minBound .. maxBound] | ||
194 | {-# INLINE mempty #-} | ||
195 | |||
196 | mappend (Caps a) (Caps b) = Caps (a .&. b) | ||
197 | {-# INLINE mappend #-} | ||
198 | |||
199 | -- | 'Handshake' compatible encoding. | ||
200 | instance Serialize Caps where | ||
201 | put (Caps caps) = S.putWord64be caps | ||
202 | {-# INLINE put #-} | ||
203 | |||
204 | get = Caps <$> S.getWord64be | ||
205 | {-# INLINE get #-} | ||
206 | |||
207 | instance Capabilities Caps where | ||
208 | type Ext Caps = Extension | ||
209 | |||
210 | allowed e (Caps caps) = (extMask e .&. caps) /= 0 | ||
211 | {-# INLINE allowed #-} | ||
212 | |||
213 | toCaps = Caps . L.foldr (.|.) 0 . L.map extMask | ||
214 | fromCaps caps = L.filter (`allowed` caps) [minBound..maxBound] | ||
215 | |||
216 | {----------------------------------------------------------------------- | ||
217 | Handshake | ||
218 | -----------------------------------------------------------------------} | ||
219 | |||
220 | maxProtocolNameSize :: Word8 | ||
221 | maxProtocolNameSize = maxBound | ||
222 | |||
223 | -- | The protocol name is used to identify to the local peer which | ||
224 | -- version of BTP the remote peer uses. | ||
225 | newtype ProtocolName = ProtocolName BS.ByteString | ||
226 | deriving (Eq, Ord, Typeable) | ||
227 | |||
228 | -- | In BTP/1.0 the name is 'BitTorrent protocol'. If this string is | ||
229 | -- different from the local peers own protocol name, then the | ||
230 | -- connection is to be dropped. | ||
231 | instance Default ProtocolName where | ||
232 | def = ProtocolName "BitTorrent protocol" | ||
233 | |||
234 | instance Show ProtocolName where | ||
235 | show (ProtocolName bs) = show bs | ||
236 | |||
237 | instance Pretty ProtocolName where | ||
238 | pPrint (ProtocolName bs) = PP.text $ BC.unpack bs | ||
239 | |||
240 | instance IsString ProtocolName where | ||
241 | fromString str | ||
242 | | L.length str <= fromIntegral maxProtocolNameSize | ||
243 | = ProtocolName (fromString str) | ||
244 | | otherwise = error $ "fromString: ProtocolName too long: " ++ str | ||
245 | |||
246 | instance Serialize ProtocolName where | ||
247 | put (ProtocolName bs) = do | ||
248 | putWord8 $ fromIntegral $ BS.length bs | ||
249 | putByteString bs | ||
250 | |||
251 | get = do | ||
252 | len <- getWord8 | ||
253 | bs <- getByteString $ fromIntegral len | ||
254 | return (ProtocolName bs) | ||
255 | |||
256 | -- | Handshake message is used to exchange all information necessary | ||
257 | -- to establish connection between peers. | ||
258 | -- | ||
259 | data Handshake = Handshake { | ||
260 | -- | Identifier of the protocol. This is usually equal to 'def'. | ||
261 | hsProtocol :: ProtocolName | ||
262 | |||
263 | -- | Reserved bytes used to specify supported BEP's. | ||
264 | , hsReserved :: Caps | ||
265 | |||
266 | -- | Info hash of the info part of the metainfo file. that is | ||
267 | -- transmitted in tracker requests. Info hash of the initiator | ||
268 | -- handshake and response handshake should match, otherwise | ||
269 | -- initiator should break the connection. | ||
270 | -- | ||
271 | , hsInfoHash :: InfoHash | ||
272 | |||
273 | -- | Peer id of the initiator. This is usually the same peer id | ||
274 | -- that is transmitted in tracker requests. | ||
275 | -- | ||
276 | , hsPeerId :: PeerId | ||
277 | |||
278 | } deriving (Show, Eq) | ||
279 | |||
280 | instance Serialize Handshake where | ||
281 | put Handshake {..} = do | ||
282 | put hsProtocol | ||
283 | put hsReserved | ||
284 | put hsInfoHash | ||
285 | put hsPeerId | ||
286 | get = Handshake <$> get <*> get <*> get <*> get | ||
287 | |||
288 | -- | Show handshake protocol string, caps and fingerprint. | ||
289 | instance Pretty Handshake where | ||
290 | pPrint Handshake {..} | ||
291 | = pPrint hsProtocol $$ | ||
292 | pPrint hsReserved $$ | ||
293 | pPrint (fingerprint hsPeerId) | ||
294 | |||
295 | -- | Get handshake message size in bytes from the length of protocol | ||
296 | -- string. | ||
297 | handshakeSize :: Word8 -> Int | ||
298 | handshakeSize n = 1 + fromIntegral n + 8 + 20 + 20 | ||
299 | |||
300 | -- | Maximum size of handshake message in bytes. | ||
301 | handshakeMaxSize :: Int | ||
302 | handshakeMaxSize = handshakeSize maxProtocolNameSize | ||
303 | |||
304 | -- | Handshake with default protocol string and reserved bitmask. | ||
305 | defaultHandshake :: InfoHash -> PeerId -> Handshake | ||
306 | defaultHandshake = Handshake def def | ||
307 | |||
308 | handshakeStats :: Handshake -> ByteStats | ||
309 | handshakeStats (Handshake (ProtocolName bs) _ _ _) | ||
310 | = ByteStats 1 (BS.length bs + 8 + 20 + 20) 0 | ||
311 | |||
312 | {----------------------------------------------------------------------- | ||
313 | -- Stats | ||
314 | -----------------------------------------------------------------------} | ||
315 | |||
316 | -- | Number of bytes. | ||
317 | type ByteCount = Int | ||
318 | |||
319 | -- | Summary of encoded message byte layout can be used to collect | ||
320 | -- stats about message flow in both directions. This data can be | ||
321 | -- retrieved using 'stats' function. | ||
322 | data ByteStats = ByteStats | ||
323 | { -- | Number of bytes used to help encode 'control' and 'payload' | ||
324 | -- bytes: message size, message ID's, etc | ||
325 | overhead :: {-# UNPACK #-} !ByteCount | ||
326 | |||
327 | -- | Number of bytes used to exchange peers state\/options: piece | ||
328 | -- and block indexes, infohash, port numbers, peer ID\/IP, etc. | ||
329 | , control :: {-# UNPACK #-} !ByteCount | ||
330 | |||
331 | -- | Number of payload bytes: torrent data blocks and infodict | ||
332 | -- metadata. | ||
333 | , payload :: {-# UNPACK #-} !ByteCount | ||
334 | } deriving Show | ||
335 | |||
336 | instance Pretty ByteStats where | ||
337 | pPrint s @ ByteStats {..} = fsep | ||
338 | [ PP.int overhead, "overhead" | ||
339 | , PP.int control, "control" | ||
340 | , PP.int payload, "payload" | ||
341 | , "bytes" | ||
342 | ] $+$ fsep | ||
343 | [ PP.int (byteLength s), "total bytes" | ||
344 | ] | ||
345 | |||
346 | -- | Empty byte sequences. | ||
347 | instance Default ByteStats where | ||
348 | def = ByteStats 0 0 0 | ||
349 | |||
350 | -- | Monoid under addition. | ||
351 | instance Monoid ByteStats where | ||
352 | mempty = def | ||
353 | mappend a b = ByteStats | ||
354 | { overhead = overhead a + overhead b | ||
355 | , control = control a + control b | ||
356 | , payload = payload a + payload b | ||
357 | } | ||
358 | |||
359 | -- | Sum of the all byte sequences. | ||
360 | byteLength :: ByteStats -> Int | ||
361 | byteLength ByteStats {..} = overhead + control + payload | ||
362 | |||
363 | {----------------------------------------------------------------------- | ||
364 | -- Regular messages | ||
365 | -----------------------------------------------------------------------} | ||
366 | |||
367 | -- | Messages which can be sent after handshaking. Minimal complete | ||
368 | -- definition: 'envelop'. | ||
369 | class PeerMessage a where | ||
370 | -- | Construct a message to be /sent/. Note that if 'ExtendedCaps' | ||
371 | -- do not contain mapping for this message the default | ||
372 | -- 'ExtendedMessageId' is used. | ||
373 | envelop :: ExtendedCaps -- ^ The /receiver/ extended capabilities; | ||
374 | -> a -- ^ An regular message; | ||
375 | -> Message -- ^ Enveloped message to sent. | ||
376 | |||
377 | -- | Find out the extension this message belong to. Can be used to | ||
378 | -- check if this message is allowed to send\/recv in current | ||
379 | -- session. | ||
380 | requires :: a -> Maybe Extension | ||
381 | requires _ = Nothing | ||
382 | |||
383 | -- | Get sizes of overhead\/control\/payload byte sequences of | ||
384 | -- binary message representation without encoding message to binary | ||
385 | -- bytestring. | ||
386 | -- | ||
387 | -- This function should obey one law: | ||
388 | -- | ||
389 | -- * 'byteLength' ('stats' msg) == 'BL.length' ('encode' msg) | ||
390 | -- | ||
391 | stats :: a -> ByteStats | ||
392 | stats _ = ByteStats 4 0 0 | ||
393 | |||
394 | {----------------------------------------------------------------------- | ||
395 | -- Status messages | ||
396 | -----------------------------------------------------------------------} | ||
397 | |||
398 | -- | Notification that the sender have updated its | ||
399 | -- 'Network.BitTorrent.Exchange.Status.PeerStatus'. | ||
400 | data StatusUpdate | ||
401 | -- | Notification that the sender will not upload data to the | ||
402 | -- receiver until unchoking happen. | ||
403 | = Choking !Bool | ||
404 | |||
405 | -- | Notification that the sender is interested (or not interested) | ||
406 | -- in any of the receiver's data pieces. | ||
407 | | Interested !Bool | ||
408 | deriving (Show, Eq, Ord, Typeable) | ||
409 | |||
410 | instance Pretty StatusUpdate where | ||
411 | pPrint (Choking False) = "not choking" | ||
412 | pPrint (Choking True ) = "choking" | ||
413 | pPrint (Interested False) = "not interested" | ||
414 | pPrint (Interested True ) = "interested" | ||
415 | |||
416 | instance PeerMessage StatusUpdate where | ||
417 | envelop _ = Status | ||
418 | {-# INLINE envelop #-} | ||
419 | |||
420 | stats _ = ByteStats 4 1 0 | ||
421 | {-# INLINE stats #-} | ||
422 | |||
423 | {----------------------------------------------------------------------- | ||
424 | -- Available messages | ||
425 | -----------------------------------------------------------------------} | ||
426 | |||
427 | -- | Messages used to inform receiver which pieces of the torrent | ||
428 | -- sender have. | ||
429 | data Available = | ||
430 | -- | Zero-based index of a piece that has just been successfully | ||
431 | -- downloaded and verified via the hash. | ||
432 | Have ! PieceIx | ||
433 | |||
434 | -- | The bitfield message may only be sent immediately after the | ||
435 | -- handshaking sequence is complete, and before any other message | ||
436 | -- are sent. If client have no pieces then bitfield need not to be | ||
437 | -- sent. | ||
438 | | Bitfield !Bitfield | ||
439 | deriving (Show, Eq) | ||
440 | |||
441 | instance Pretty Available where | ||
442 | pPrint (Have ix ) = "Have" <+> int ix | ||
443 | pPrint (Bitfield _ ) = "Bitfield" | ||
444 | |||
445 | instance PeerMessage Available where | ||
446 | envelop _ = Available | ||
447 | {-# INLINE envelop #-} | ||
448 | |||
449 | stats (Have _) = ByteStats (4 + 1) 4 0 | ||
450 | stats (Bitfield bf) = ByteStats (4 + 1) (q + trailing) 0 | ||
451 | where | ||
452 | trailing = if r == 0 then 0 else 1 | ||
453 | (q, r) = quotRem (totalCount bf) 8 | ||
454 | |||
455 | {----------------------------------------------------------------------- | ||
456 | -- Transfer messages | ||
457 | -----------------------------------------------------------------------} | ||
458 | |||
459 | -- | Messages used to transfer 'Block's. | ||
460 | data Transfer | ||
461 | -- | Request for a particular block. If a client is requested a | ||
462 | -- block that another peer do not have the peer might not answer | ||
463 | -- at all. | ||
464 | = Request ! BlockIx | ||
465 | |||
466 | -- | Response to a request for a block. | ||
467 | | Piece !(Block BL.ByteString) | ||
468 | |||
469 | -- | Used to cancel block requests. It is typically used during | ||
470 | -- "End Game". | ||
471 | | Cancel !BlockIx | ||
472 | deriving (Show, Eq) | ||
473 | |||
474 | instance Pretty Transfer where | ||
475 | pPrint (Request ix ) = "Request" <+> pPrint ix | ||
476 | pPrint (Piece blk) = "Piece" <+> pPrint blk | ||
477 | pPrint (Cancel i ) = "Cancel" <+> pPrint i | ||
478 | |||
479 | instance PeerMessage Transfer where | ||
480 | envelop _ = Transfer | ||
481 | {-# INLINE envelop #-} | ||
482 | |||
483 | stats (Request _ ) = ByteStats (4 + 1) (3 * 4) 0 | ||
484 | stats (Piece p ) = ByteStats (4 + 1) (4 + 4 + blockSize p) 0 | ||
485 | stats (Cancel _ ) = ByteStats (4 + 1) (3 * 4) 0 | ||
486 | |||
487 | -- TODO increase | ||
488 | -- | Max number of pending 'Request's inflight. | ||
489 | defaultRequestQueueLength :: Int | ||
490 | defaultRequestQueueLength = 1 | ||
491 | |||
492 | {----------------------------------------------------------------------- | ||
493 | -- Fast messages | ||
494 | -----------------------------------------------------------------------} | ||
495 | |||
496 | -- | BEP6 messages. | ||
497 | data FastMessage = | ||
498 | -- | If a peer have all pieces it might send the 'HaveAll' message | ||
499 | -- instead of 'Bitfield' message. Used to save bandwidth. | ||
500 | HaveAll | ||
501 | |||
502 | -- | If a peer have no pieces it might send 'HaveNone' message | ||
503 | -- intead of 'Bitfield' message. Used to save bandwidth. | ||
504 | | HaveNone | ||
505 | |||
506 | -- | This is an advisory message meaning "you might like to | ||
507 | -- download this piece." Used to avoid excessive disk seeks and | ||
508 | -- amount of IO. | ||
509 | | SuggestPiece !PieceIx | ||
510 | |||
511 | -- | Notifies a requesting peer that its request will not be | ||
512 | -- satisfied. | ||
513 | | RejectRequest !BlockIx | ||
514 | |||
515 | -- | This is an advisory messsage meaning \"if you ask for this | ||
516 | -- piece, I'll give it to you even if you're choked.\" Used to | ||
517 | -- shorten starting phase. | ||
518 | | AllowedFast !PieceIx | ||
519 | deriving (Show, Eq) | ||
520 | |||
521 | instance Pretty FastMessage where | ||
522 | pPrint (HaveAll ) = "Have all" | ||
523 | pPrint (HaveNone ) = "Have none" | ||
524 | pPrint (SuggestPiece pix) = "Suggest" <+> int pix | ||
525 | pPrint (RejectRequest bix) = "Reject" <+> pPrint bix | ||
526 | pPrint (AllowedFast pix) = "Allowed fast" <+> int pix | ||
527 | |||
528 | instance PeerMessage FastMessage where | ||
529 | envelop _ = Fast | ||
530 | {-# INLINE envelop #-} | ||
531 | |||
532 | requires _ = Just ExtFast | ||
533 | {-# INLINE requires #-} | ||
534 | |||
535 | stats HaveAll = ByteStats 4 1 0 | ||
536 | stats HaveNone = ByteStats 4 1 0 | ||
537 | stats (SuggestPiece _) = ByteStats 5 4 0 | ||
538 | stats (RejectRequest _) = ByteStats 5 12 0 | ||
539 | stats (AllowedFast _) = ByteStats 5 4 0 | ||
540 | |||
541 | {----------------------------------------------------------------------- | ||
542 | -- Extension protocol | ||
543 | -----------------------------------------------------------------------} | ||
544 | |||
545 | {----------------------------------------------------------------------- | ||
546 | -- Extended capabilities | ||
547 | -----------------------------------------------------------------------} | ||
548 | |||
549 | data ExtendedExtension | ||
550 | = ExtMetadata -- ^ BEP 9: Extension for Peers to Send Metadata Files | ||
551 | deriving (Show, Eq, Ord, Enum, Bounded, Typeable) | ||
552 | |||
553 | instance IsString ExtendedExtension where | ||
554 | fromString = fromMaybe (error msg) . fromKey . fromString | ||
555 | where | ||
556 | msg = "fromString: could not parse ExtendedExtension" | ||
557 | |||
558 | instance Pretty ExtendedExtension where | ||
559 | pPrint ExtMetadata = "Extension for Peers to Send Metadata Files" | ||
560 | |||
561 | fromKey :: BKey -> Maybe ExtendedExtension | ||
562 | fromKey "ut_metadata" = Just ExtMetadata | ||
563 | fromKey _ = Nothing | ||
564 | {-# INLINE fromKey #-} | ||
565 | |||
566 | toKey :: ExtendedExtension -> BKey | ||
567 | toKey ExtMetadata = "ut_metadata" | ||
568 | {-# INLINE toKey #-} | ||
569 | |||
570 | type ExtendedMessageId = Word8 | ||
571 | |||
572 | extId :: ExtendedExtension -> ExtendedMessageId | ||
573 | extId ExtMetadata = 1 | ||
574 | {-# INLINE extId #-} | ||
575 | |||
576 | type ExtendedMap = Map ExtendedExtension ExtendedMessageId | ||
577 | |||
578 | -- | The extension IDs must be stored for every peer, because every | ||
579 | -- peer may have different IDs for the same extension. | ||
580 | -- | ||
581 | newtype ExtendedCaps = ExtendedCaps { extendedCaps :: ExtendedMap } | ||
582 | deriving (Show, Eq) | ||
583 | |||
584 | instance Pretty ExtendedCaps where | ||
585 | pPrint = ppCaps | ||
586 | {-# INLINE pPrint #-} | ||
587 | |||
588 | -- | The empty set. | ||
589 | instance Default ExtendedCaps where | ||
590 | def = ExtendedCaps M.empty | ||
591 | |||
592 | -- | Monoid under intersection: | ||
593 | -- | ||
594 | -- * The 'mempty' caps includes all known extensions; | ||
595 | -- | ||
596 | -- * the 'mappend' operation is NOT commutative: it return message | ||
597 | -- id from the first caps for the extensions existing in both caps. | ||
598 | -- | ||
599 | instance Monoid ExtendedCaps where | ||
600 | mempty = toCaps [minBound..maxBound] | ||
601 | mappend (ExtendedCaps a) (ExtendedCaps b) = | ||
602 | ExtendedCaps (M.intersection a b) | ||
603 | |||
604 | appendBDict :: BDict -> ExtendedMap -> ExtendedMap | ||
605 | appendBDict (Cons key val xs) caps | ||
606 | | Just ext <- fromKey key | ||
607 | , Right eid <- fromBEncode val = M.insert ext eid (appendBDict xs caps) | ||
608 | | otherwise = appendBDict xs caps | ||
609 | appendBDict Nil caps = caps | ||
610 | |||
611 | -- | Handshake compatible encoding. | ||
612 | instance BEncode ExtendedCaps where | ||
613 | toBEncode = BDict . BE.fromAscList . L.sortBy (comparing fst) | ||
614 | . L.map (toKey *** toBEncode) . M.toList . extendedCaps | ||
615 | |||
616 | fromBEncode (BDict bd) = pure $ ExtendedCaps $ appendBDict bd M.empty | ||
617 | fromBEncode _ = decodingError "ExtendedCaps" | ||
618 | |||
619 | instance Capabilities ExtendedCaps where | ||
620 | type Ext ExtendedCaps = ExtendedExtension | ||
621 | |||
622 | toCaps = ExtendedCaps . M.fromList . L.map (id &&& extId) | ||
623 | |||
624 | fromCaps = M.keys . extendedCaps | ||
625 | {-# INLINE fromCaps #-} | ||
626 | |||
627 | allowed e (ExtendedCaps caps) = M.member e caps | ||
628 | {-# INLINE allowed #-} | ||
629 | |||
630 | remoteMessageId :: ExtendedExtension -> ExtendedCaps -> ExtendedMessageId | ||
631 | remoteMessageId ext = fromMaybe (extId ext) . M.lookup ext . extendedCaps | ||
632 | |||
633 | {----------------------------------------------------------------------- | ||
634 | -- Extended handshake | ||
635 | -----------------------------------------------------------------------} | ||
636 | |||
637 | -- | This message should be sent immediately after the standard | ||
638 | -- bittorrent handshake to any peer that supports this extension | ||
639 | -- protocol. Extended handshakes can be sent more than once, however | ||
640 | -- an implementation may choose to ignore subsequent handshake | ||
641 | -- messages. | ||
642 | -- | ||
643 | data ExtendedHandshake = ExtendedHandshake | ||
644 | { -- | If this peer has an IPv4 interface, this is the compact | ||
645 | -- representation of that address. | ||
646 | ehsIPv4 :: Maybe HostAddress | ||
647 | |||
648 | -- | If this peer has an IPv6 interface, this is the compact | ||
649 | -- representation of that address. | ||
650 | , ehsIPv6 :: Maybe HostAddress6 | ||
651 | |||
652 | -- | Dictionary of supported extension messages which maps names | ||
653 | -- of extensions to an extended message ID for each extension | ||
654 | -- message. | ||
655 | , ehsCaps :: ExtendedCaps | ||
656 | |||
657 | -- | Size of 'Data.Torrent.InfoDict' in bytes. This field should | ||
658 | -- be added if 'ExtMetadata' is enabled in current session /and/ | ||
659 | -- peer have the torrent file. | ||
660 | , ehsMetadataSize :: Maybe Int | ||
661 | |||
662 | -- | Local TCP /listen/ port. Allows each side to learn about the | ||
663 | -- TCP port number of the other side. | ||
664 | , ehsPort :: Maybe PortNumber | ||
665 | |||
666 | -- | Request queue the number of outstanding 'Request' messages | ||
667 | -- this client supports without dropping any. | ||
668 | , ehsQueueLength :: Maybe Int | ||
669 | |||
670 | -- | Client name and version. | ||
671 | , ehsVersion :: Maybe Text | ||
672 | |||
673 | -- | IP of the remote end | ||
674 | , ehsYourIp :: Maybe IP | ||
675 | } deriving (Show, Eq, Typeable) | ||
676 | |||
677 | extHandshakeId :: ExtendedMessageId | ||
678 | extHandshakeId = 0 | ||
679 | |||
680 | -- | Default 'Request' queue size. | ||
681 | defaultQueueLength :: Int | ||
682 | defaultQueueLength = 1 | ||
683 | |||
684 | -- | All fields are empty. | ||
685 | instance Default ExtendedHandshake where | ||
686 | def = ExtendedHandshake def def def def def def def def | ||
687 | |||
688 | instance Monoid ExtendedHandshake where | ||
689 | mempty = def { ehsCaps = mempty } | ||
690 | mappend old new = ExtendedHandshake { | ||
691 | ehsCaps = ehsCaps old <> ehsCaps new, | ||
692 | ehsIPv4 = ehsIPv4 old `mergeOld` ehsIPv4 new, | ||
693 | ehsIPv6 = ehsIPv6 old `mergeOld` ehsIPv6 new, | ||
694 | ehsMetadataSize = ehsMetadataSize old `mergeNew` ehsMetadataSize new, | ||
695 | ehsPort = ehsPort old `mergeOld` ehsPort new, | ||
696 | ehsQueueLength = ehsQueueLength old `mergeNew` ehsQueueLength new, | ||
697 | ehsVersion = ehsVersion old `mergeOld` ehsVersion new, | ||
698 | ehsYourIp = ehsYourIp old `mergeOld` ehsYourIp new | ||
699 | } | ||
700 | where | ||
701 | mergeOld mold mnew = mold <|> mnew | ||
702 | mergeNew mold mnew = mnew <|> mold | ||
703 | |||
704 | |||
705 | instance BEncode ExtendedHandshake where | ||
706 | toBEncode ExtendedHandshake {..} = toDict $ | ||
707 | "ipv4" .=? (S.encode <$> ehsIPv4) | ||
708 | .: "ipv6" .=? (S.encode <$> ehsIPv6) | ||
709 | .: "m" .=! ehsCaps | ||
710 | .: "metadata_size" .=? ehsMetadataSize | ||
711 | .: "p" .=? ehsPort | ||
712 | .: "reqq" .=? ehsQueueLength | ||
713 | .: "v" .=? ehsVersion | ||
714 | .: "yourip" .=? (runPut <$> either put put <$> toEither <$> ehsYourIp) | ||
715 | .: endDict | ||
716 | where | ||
717 | toEither (IPv4 v4) = Left v4 | ||
718 | toEither (IPv6 v6) = Right v6 | ||
719 | |||
720 | fromBEncode = fromDict $ ExtendedHandshake | ||
721 | <$>? "ipv4" | ||
722 | <*>? "ipv6" | ||
723 | <*>! "m" | ||
724 | <*>? "metadata_size" | ||
725 | <*>? "p" | ||
726 | <*>? "reqq" | ||
727 | <*>? "v" | ||
728 | <*> (opt "yourip" >>= getYourIp) | ||
729 | |||
730 | getYourIp :: Maybe BValue -> BE.Get (Maybe IP) | ||
731 | getYourIp f = | ||
732 | return $ do | ||
733 | BString ip <- f | ||
734 | either (const Nothing) Just $ | ||
735 | case BS.length ip of | ||
736 | 4 -> IPv4 <$> S.decode ip | ||
737 | 16 -> IPv6 <$> S.decode ip | ||
738 | _ -> fail "" | ||
739 | |||
740 | instance Pretty ExtendedHandshake where | ||
741 | pPrint = PP.text . show | ||
742 | |||
743 | -- | NOTE: Approximated 'stats'. | ||
744 | instance PeerMessage ExtendedHandshake where | ||
745 | envelop c = envelop c . EHandshake | ||
746 | {-# INLINE envelop #-} | ||
747 | |||
748 | requires _ = Just ExtExtended | ||
749 | {-# INLINE requires #-} | ||
750 | |||
751 | stats _ = ByteStats (4 + 1 + 1) 100 {- is it ok? -} 0 -- FIXME | ||
752 | {-# INLINE stats #-} | ||
753 | |||
754 | -- | Set default values and the specified 'ExtendedCaps'. | ||
755 | nullExtendedHandshake :: ExtendedCaps -> ExtendedHandshake | ||
756 | nullExtendedHandshake caps = ExtendedHandshake | ||
757 | { ehsIPv4 = Nothing | ||
758 | , ehsIPv6 = Nothing | ||
759 | , ehsCaps = caps | ||
760 | , ehsMetadataSize = Nothing | ||
761 | , ehsPort = Nothing | ||
762 | , ehsQueueLength = Just defaultQueueLength | ||
763 | , ehsVersion = Just $ T.pack $ render $ pPrint libFingerprint | ||
764 | , ehsYourIp = Nothing | ||
765 | } | ||
766 | |||
767 | {----------------------------------------------------------------------- | ||
768 | -- Metadata exchange extension | ||
769 | -----------------------------------------------------------------------} | ||
770 | |||
771 | -- | A peer MUST verify that any piece it sends passes the info-hash | ||
772 | -- verification. i.e. until the peer has the entire metadata, it | ||
773 | -- cannot run SHA-1 to verify that it yields the same hash as the | ||
774 | -- info-hash. | ||
775 | -- | ||
776 | data ExtendedMetadata | ||
777 | -- | This message requests the a specified metadata piece. The | ||
778 | -- response to this message, from a peer supporting the extension, | ||
779 | -- is either a 'MetadataReject' or a 'MetadataData' message. | ||
780 | = MetadataRequest PieceIx | ||
781 | |||
782 | -- | If sender requested a valid 'PieceIx' and receiver have the | ||
783 | -- corresponding piece then receiver should respond with this | ||
784 | -- message. | ||
785 | | MetadataData | ||
786 | { -- | A piece of 'Data.Torrent.InfoDict'. | ||
787 | piece :: P.Piece BS.ByteString | ||
788 | |||
789 | -- | This key has the same semantics as the 'ehsMetadataSize' in | ||
790 | -- the 'ExtendedHandshake' — it is size of the torrent info | ||
791 | -- dict. | ||
792 | , totalSize :: Int | ||
793 | } | ||
794 | |||
795 | -- | Peers that do not have the entire metadata MUST respond with | ||
796 | -- a reject message to any metadata request. | ||
797 | -- | ||
798 | -- Clients MAY implement flood protection by rejecting request | ||
799 | -- messages after a certain number of them have been | ||
800 | -- served. Typically the number of pieces of metadata times a | ||
801 | -- factor. | ||
802 | | MetadataReject PieceIx | ||
803 | |||
804 | -- | Reserved. By specification we should ignore unknown metadata | ||
805 | -- messages. | ||
806 | | MetadataUnknown BValue | ||
807 | deriving (Show, Eq, Typeable) | ||
808 | |||
809 | -- | Extended metadata message id used in 'msg_type_key'. | ||
810 | type MetadataId = Int | ||
811 | |||
812 | msg_type_key, piece_key, total_size_key :: BKey | ||
813 | msg_type_key = "msg_type" | ||
814 | piece_key = "piece" | ||
815 | total_size_key = "total_size" | ||
816 | |||
817 | -- | BEP9 compatible encoding. | ||
818 | instance BEncode ExtendedMetadata where | ||
819 | toBEncode (MetadataRequest pix) = toDict $ | ||
820 | msg_type_key .=! (0 :: MetadataId) | ||
821 | .: piece_key .=! pix | ||
822 | .: endDict | ||
823 | toBEncode (MetadataData (P.Piece pix _) totalSize) = toDict $ | ||
824 | msg_type_key .=! (1 :: MetadataId) | ||
825 | .: piece_key .=! pix | ||
826 | .: total_size_key .=! totalSize | ||
827 | .: endDict | ||
828 | toBEncode (MetadataReject pix) = toDict $ | ||
829 | msg_type_key .=! (2 :: MetadataId) | ||
830 | .: piece_key .=! pix | ||
831 | .: endDict | ||
832 | toBEncode (MetadataUnknown bval) = bval | ||
833 | |||
834 | fromBEncode bval = (`fromDict` bval) $ do | ||
835 | mid <- field $ req msg_type_key | ||
836 | case mid :: MetadataId of | ||
837 | 0 -> MetadataRequest <$>! piece_key | ||
838 | 1 -> metadataData <$>! piece_key <*>! total_size_key | ||
839 | 2 -> MetadataReject <$>! piece_key | ||
840 | _ -> pure (MetadataUnknown bval) | ||
841 | where | ||
842 | metadataData pix s = MetadataData (P.Piece pix BS.empty) s | ||
843 | |||
844 | -- | Piece data bytes are omitted. | ||
845 | instance Pretty ExtendedMetadata where | ||
846 | pPrint (MetadataRequest pix ) = "Request" <+> PP.int pix | ||
847 | pPrint (MetadataData p t) = "Data" <+> pPrint p <+> PP.int t | ||
848 | pPrint (MetadataReject pix ) = "Reject" <+> PP.int pix | ||
849 | pPrint (MetadataUnknown bval ) = "Unknown" <+> ppBEncode bval | ||
850 | |||
851 | -- | NOTE: Approximated 'stats'. | ||
852 | instance PeerMessage ExtendedMetadata where | ||
853 | envelop c = envelop c . EMetadata (remoteMessageId ExtMetadata c) | ||
854 | {-# INLINE envelop #-} | ||
855 | |||
856 | requires _ = Just ExtExtended | ||
857 | {-# INLINE requires #-} | ||
858 | |||
859 | stats (MetadataRequest _) = ByteStats (4 + 1 + 1) {- ~ -} 25 0 | ||
860 | stats (MetadataData p _) = ByteStats (4 + 1 + 1) {- ~ -} 41 $ | ||
861 | BS.length (P.pieceData p) | ||
862 | stats (MetadataReject _) = ByteStats (4 + 1 + 1) {- ~ -} 25 0 | ||
863 | stats (MetadataUnknown _) = ByteStats (4 + 1 + 1) {- ? -} 0 0 | ||
864 | |||
865 | -- | All 'Piece's in 'MetadataData' messages MUST have size equal to | ||
866 | -- this value. The last trailing piece can be shorter. | ||
867 | metadataPieceSize :: PieceSize | ||
868 | metadataPieceSize = 16 * 1024 | ||
869 | |||
870 | isLastPiece :: P.Piece a -> Int -> Bool | ||
871 | isLastPiece P.Piece {..} total = succ pieceIndex == pcnt | ||
872 | where | ||
873 | pcnt = q + if r > 0 then 1 else 0 | ||
874 | (q, r) = quotRem total metadataPieceSize | ||
875 | |||
876 | -- TODO we can check if the piece payload bytestring have appropriate | ||
877 | -- length; otherwise serialization MUST fail. | ||
878 | isValidPiece :: P.Piece BL.ByteString -> Int -> Bool | ||
879 | isValidPiece p @ P.Piece {..} total | ||
880 | | isLastPiece p total = pieceSize p <= metadataPieceSize | ||
881 | | otherwise = pieceSize p == metadataPieceSize | ||
882 | |||
883 | setMetadataPayload :: BS.ByteString -> ExtendedMetadata -> ExtendedMetadata | ||
884 | setMetadataPayload bs (MetadataData (P.Piece pix _) t) = | ||
885 | MetadataData (P.Piece pix bs) t | ||
886 | setMetadataPayload _ msg = msg | ||
887 | |||
888 | getMetadataPayload :: ExtendedMetadata -> Maybe BS.ByteString | ||
889 | getMetadataPayload (MetadataData (P.Piece _ bs) _) = Just bs | ||
890 | getMetadataPayload _ = Nothing | ||
891 | |||
892 | -- | Metadata BDict usually contain only 'msg_type_key', 'piece_key' | ||
893 | -- and 'total_size_key' fields so it normally should take less than | ||
894 | -- 100 bytes. This limit is two order of magnitude larger to be | ||
895 | -- permissive to 'MetadataUnknown' messages. | ||
896 | -- | ||
897 | -- See 'maxMessageSize' for further explanation. | ||
898 | -- | ||
899 | maxMetadataBDictSize :: Int | ||
900 | maxMetadataBDictSize = 16 * 1024 | ||
901 | |||
902 | maxMetadataSize :: Int | ||
903 | maxMetadataSize = maxMetadataBDictSize + metadataPieceSize | ||
904 | |||
905 | -- to make MetadataData constructor fields a little bit prettier we | ||
906 | -- cheat here: first we read empty 'pieceData' from bdict, but then we | ||
907 | -- fill that field with the actual piece data — trailing bytes of | ||
908 | -- the message | ||
909 | getMetadata :: Int -> S.Get ExtendedMetadata | ||
910 | getMetadata len | ||
911 | | len > maxMetadataSize = fail $ parseError "size exceeded limit" | ||
912 | | otherwise = do | ||
913 | bs <- getByteString len | ||
914 | parseRes $ BS.parse BE.parser bs | ||
915 | where | ||
916 | parseError reason = "unable to parse metadata message: " ++ reason | ||
917 | |||
918 | parseRes (BS.Fail _ _ m) = fail $ parseError $ "bdict: " ++ m | ||
919 | parseRes (BS.Partial _) = fail $ parseError "bdict: not enough bytes" | ||
920 | parseRes (BS.Done piece bvalueBS) | ||
921 | | BS.length piece > metadataPieceSize | ||
922 | = fail "infodict piece: size exceeded limit" | ||
923 | | otherwise = do | ||
924 | metadata <- either (fail . parseError) pure $ fromBEncode bvalueBS | ||
925 | return $ setMetadataPayload piece metadata | ||
926 | |||
927 | putMetadata :: ExtendedMetadata -> BL.ByteString | ||
928 | putMetadata msg | ||
929 | | Just bs <- getMetadataPayload msg = BE.encode msg <> BL.fromStrict bs | ||
930 | | otherwise = BE.encode msg | ||
931 | |||
932 | -- | Allows a requesting peer to send 2 'MetadataRequest's for the | ||
933 | -- each piece. | ||
934 | -- | ||
935 | -- See 'Network.BitTorrent.Wire.Options.metadataFactor' for | ||
936 | -- explanation why do we need this limit. | ||
937 | defaultMetadataFactor :: Int | ||
938 | defaultMetadataFactor = 2 | ||
939 | |||
940 | -- | Usually torrent size do not exceed 1MB. This value limit torrent | ||
941 | -- /content/ size to about 8TB. | ||
942 | -- | ||
943 | -- See 'Network.BitTorrent.Wire.Options.maxInfoDictSize' for | ||
944 | -- explanation why do we need this limit. | ||
945 | defaultMaxInfoDictSize :: Int | ||
946 | defaultMaxInfoDictSize = 10 * 1024 * 1024 | ||
947 | |||
948 | {----------------------------------------------------------------------- | ||
949 | -- Extension protocol messages | ||
950 | -----------------------------------------------------------------------} | ||
951 | |||
952 | -- | For more info see <http://www.bittorrent.org/beps/bep_0010.html> | ||
953 | data ExtendedMessage | ||
954 | = EHandshake ExtendedHandshake | ||
955 | | EMetadata ExtendedMessageId ExtendedMetadata | ||
956 | | EUnknown ExtendedMessageId BS.ByteString | ||
957 | deriving (Show, Eq, Typeable) | ||
958 | |||
959 | instance Pretty ExtendedMessage where | ||
960 | pPrint (EHandshake ehs) = pPrint ehs | ||
961 | pPrint (EMetadata _ msg) = "Metadata" <+> pPrint msg | ||
962 | pPrint (EUnknown mid _ ) = "Unknown" <+> PP.text (show mid) | ||
963 | |||
964 | instance PeerMessage ExtendedMessage where | ||
965 | envelop _ = Extended | ||
966 | {-# INLINE envelop #-} | ||
967 | |||
968 | requires _ = Just ExtExtended | ||
969 | {-# INLINE requires #-} | ||
970 | |||
971 | stats (EHandshake hs) = stats hs | ||
972 | stats (EMetadata _ msg) = stats msg | ||
973 | stats (EUnknown _ msg) = ByteStats (4 + 1 + 1) (BS.length msg) 0 | ||
974 | |||
975 | {----------------------------------------------------------------------- | ||
976 | -- The message datatype | ||
977 | -----------------------------------------------------------------------} | ||
978 | |||
979 | type MessageId = Word8 | ||
980 | |||
981 | -- | Messages used in communication between peers. | ||
982 | -- | ||
983 | -- Note: If some extensions are disabled (not present in extension | ||
984 | -- mask) and client receive message used by the disabled | ||
985 | -- extension then the client MUST close the connection. | ||
986 | -- | ||
987 | data Message | ||
988 | -- | Peers may close the TCP connection if they have not received | ||
989 | -- any messages for a given period of time, generally 2 | ||
990 | -- minutes. Thus, the KeepAlive message is sent to keep the | ||
991 | -- connection between two peers alive, if no /other/ message has | ||
992 | -- been sent in a given period of time. | ||
993 | = KeepAlive | ||
994 | | Status !StatusUpdate -- ^ Messages used to update peer status. | ||
995 | | Available !Available -- ^ Messages used to inform availability. | ||
996 | | Transfer !Transfer -- ^ Messages used to transfer 'Block's. | ||
997 | |||
998 | -- | Peer receiving a handshake indicating the remote peer | ||
999 | -- supports the 'ExtDHT' should send a 'Port' message. Peers that | ||
1000 | -- receive this message should attempt to ping the node on the | ||
1001 | -- received port and IP address of the remote peer. | ||
1002 | | Port !PortNumber | ||
1003 | | Fast !FastMessage | ||
1004 | | Extended !ExtendedMessage | ||
1005 | deriving (Show, Eq) | ||
1006 | |||
1007 | instance Default Message where | ||
1008 | def = KeepAlive | ||
1009 | {-# INLINE def #-} | ||
1010 | |||
1011 | -- | Payload bytes are omitted. | ||
1012 | instance Pretty Message where | ||
1013 | pPrint (KeepAlive ) = "Keep alive" | ||
1014 | pPrint (Status m) = "Status" <+> pPrint m | ||
1015 | pPrint (Available m) = pPrint m | ||
1016 | pPrint (Transfer m) = pPrint m | ||
1017 | pPrint (Port p) = "Port" <+> int (fromEnum p) | ||
1018 | pPrint (Fast m) = pPrint m | ||
1019 | pPrint (Extended m) = pPrint m | ||
1020 | |||
1021 | instance PeerMessage Message where | ||
1022 | envelop _ = id | ||
1023 | {-# INLINE envelop #-} | ||
1024 | |||
1025 | requires KeepAlive = Nothing | ||
1026 | requires (Status _) = Nothing | ||
1027 | requires (Available _) = Nothing | ||
1028 | requires (Transfer _) = Nothing | ||
1029 | requires (Port _) = Just ExtDHT | ||
1030 | requires (Fast _) = Just ExtFast | ||
1031 | requires (Extended _) = Just ExtExtended | ||
1032 | |||
1033 | stats KeepAlive = ByteStats 4 0 0 | ||
1034 | stats (Status m) = stats m | ||
1035 | stats (Available m) = stats m | ||
1036 | stats (Transfer m) = stats m | ||
1037 | stats (Port _) = ByteStats 5 2 0 | ||
1038 | stats (Fast m) = stats m | ||
1039 | stats (Extended m) = stats m | ||
1040 | |||
1041 | -- | PORT message. | ||
1042 | instance PeerMessage PortNumber where | ||
1043 | envelop _ = Port | ||
1044 | {-# INLINE envelop #-} | ||
1045 | |||
1046 | requires _ = Just ExtDHT | ||
1047 | {-# INLINE requires #-} | ||
1048 | |||
1049 | -- | How long /this/ peer should wait before dropping connection, in | ||
1050 | -- seconds. | ||
1051 | defaultKeepAliveTimeout :: Int | ||
1052 | defaultKeepAliveTimeout = 2 * 60 | ||
1053 | |||
1054 | -- | How often /this/ peer should send 'KeepAlive' messages, in | ||
1055 | -- seconds. | ||
1056 | defaultKeepAliveInterval :: Int | ||
1057 | defaultKeepAliveInterval = 60 | ||
1058 | |||
1059 | getInt :: S.Get Int | ||
1060 | getInt = fromIntegral <$> S.getWord32be | ||
1061 | {-# INLINE getInt #-} | ||
1062 | |||
1063 | putInt :: S.Putter Int | ||
1064 | putInt = S.putWord32be . fromIntegral | ||
1065 | {-# INLINE putInt #-} | ||
1066 | |||
1067 | -- | This limit should protect against "out-of-memory" attacks: if a | ||
1068 | -- malicious peer have sent a long varlength message then receiver can | ||
1069 | -- accumulate too long bytestring in the 'Get'. | ||
1070 | -- | ||
1071 | -- Normal messages should never exceed this limits. | ||
1072 | -- | ||
1073 | -- See also 'maxBitfieldSize', 'maxBlockSize' limits. | ||
1074 | -- | ||
1075 | maxMessageSize :: Int | ||
1076 | maxMessageSize = 20 + 1024 * 1024 | ||
1077 | |||
1078 | -- | This also limit max torrent size to: | ||
1079 | -- | ||
1080 | -- max_bitfield_size * piece_ix_per_byte * max_piece_size = | ||
1081 | -- 2 ^ 20 * 8 * 1MB = | ||
1082 | -- 8TB | ||
1083 | -- | ||
1084 | maxBitfieldSize :: Int | ||
1085 | maxBitfieldSize = 1024 * 1024 | ||
1086 | |||
1087 | getBitfield :: Int -> S.Get Bitfield | ||
1088 | getBitfield len | ||
1089 | | len > maxBitfieldSize = fail "BITFIELD message size exceeded limit" | ||
1090 | | otherwise = fromBitmap <$> getByteString len | ||
1091 | |||
1092 | maxBlockSize :: Int | ||
1093 | maxBlockSize = 4 * defaultTransferSize | ||
1094 | |||
1095 | getBlock :: Int -> S.Get (Block BL.ByteString) | ||
1096 | getBlock len | ||
1097 | | len > maxBlockSize = fail "BLOCK message size exceeded limit" | ||
1098 | | otherwise = Block <$> getInt <*> getInt | ||
1099 | <*> getLazyByteString (fromIntegral len) | ||
1100 | {-# INLINE getBlock #-} | ||
1101 | |||
1102 | instance Serialize Message where | ||
1103 | get = do | ||
1104 | len <- getInt | ||
1105 | |||
1106 | when (len > maxMessageSize) $ do | ||
1107 | fail "message body size exceeded the limit" | ||
1108 | |||
1109 | if len == 0 then return KeepAlive | ||
1110 | else do | ||
1111 | mid <- S.getWord8 | ||
1112 | case mid of | ||
1113 | 0x00 -> return $ Status (Choking True) | ||
1114 | 0x01 -> return $ Status (Choking False) | ||
1115 | 0x02 -> return $ Status (Interested True) | ||
1116 | 0x03 -> return $ Status (Interested False) | ||
1117 | 0x04 -> (Available . Have) <$> getInt | ||
1118 | 0x05 -> (Available . Bitfield) <$> getBitfield (pred len) | ||
1119 | 0x06 -> (Transfer . Request) <$> S.get | ||
1120 | 0x07 -> (Transfer . Piece) <$> getBlock (len - 9) | ||
1121 | 0x08 -> (Transfer . Cancel) <$> S.get | ||
1122 | 0x09 -> Port <$> S.get | ||
1123 | 0x0D -> (Fast . SuggestPiece) <$> getInt | ||
1124 | 0x0E -> return $ Fast HaveAll | ||
1125 | 0x0F -> return $ Fast HaveNone | ||
1126 | 0x10 -> (Fast . RejectRequest) <$> S.get | ||
1127 | 0x11 -> (Fast . AllowedFast) <$> getInt | ||
1128 | 0x14 -> Extended <$> getExtendedMessage (pred len) | ||
1129 | _ -> do | ||
1130 | rm <- S.remaining >>= S.getBytes | ||
1131 | fail $ "unknown message ID: " ++ show mid ++ "\n" | ||
1132 | ++ "remaining available bytes: " ++ show rm | ||
1133 | |||
1134 | put KeepAlive = putInt 0 | ||
1135 | put (Status msg) = putStatus msg | ||
1136 | put (Available msg) = putAvailable msg | ||
1137 | put (Transfer msg) = putTransfer msg | ||
1138 | put (Port p ) = putPort p | ||
1139 | put (Fast msg) = putFast msg | ||
1140 | put (Extended m ) = putExtendedMessage m | ||
1141 | |||
1142 | statusUpdateId :: StatusUpdate -> MessageId | ||
1143 | statusUpdateId (Choking choking) = fromIntegral (0 + fromEnum choking) | ||
1144 | statusUpdateId (Interested choking) = fromIntegral (2 + fromEnum choking) | ||
1145 | |||
1146 | putStatus :: Putter StatusUpdate | ||
1147 | putStatus su = do | ||
1148 | putInt 1 | ||
1149 | putWord8 (statusUpdateId su) | ||
1150 | |||
1151 | putAvailable :: Putter Available | ||
1152 | putAvailable (Have i) = do | ||
1153 | putInt 5 | ||
1154 | putWord8 0x04 | ||
1155 | putInt i | ||
1156 | putAvailable (Bitfield (toBitmap -> bs)) = do | ||
1157 | putInt $ 1 + fromIntegral (BL.length bs) | ||
1158 | putWord8 0x05 | ||
1159 | putLazyByteString bs | ||
1160 | |||
1161 | putBlock :: Putter (Block BL.ByteString) | ||
1162 | putBlock Block {..} = do | ||
1163 | putInt blkPiece | ||
1164 | putInt blkOffset | ||
1165 | putLazyByteString blkData | ||
1166 | |||
1167 | putTransfer :: Putter Transfer | ||
1168 | putTransfer (Request blk) = putInt 13 >> S.putWord8 0x06 >> S.put blk | ||
1169 | putTransfer (Piece blk) = do | ||
1170 | putInt (9 + blockSize blk) | ||
1171 | putWord8 0x07 | ||
1172 | putBlock blk | ||
1173 | putTransfer (Cancel blk) = putInt 13 >> S.putWord8 0x08 >> S.put blk | ||
1174 | |||
1175 | putPort :: Putter PortNumber | ||
1176 | putPort p = do | ||
1177 | putInt 3 | ||
1178 | putWord8 0x09 | ||
1179 | put p | ||
1180 | |||
1181 | putFast :: Putter FastMessage | ||
1182 | putFast HaveAll = putInt 1 >> putWord8 0x0E | ||
1183 | putFast HaveNone = putInt 1 >> putWord8 0x0F | ||
1184 | putFast (SuggestPiece pix) = putInt 5 >> putWord8 0x0D >> putInt pix | ||
1185 | putFast (RejectRequest i ) = putInt 13 >> putWord8 0x10 >> put i | ||
1186 | putFast (AllowedFast i ) = putInt 5 >> putWord8 0x11 >> putInt i | ||
1187 | |||
1188 | maxEHandshakeSize :: Int | ||
1189 | maxEHandshakeSize = 16 * 1024 | ||
1190 | |||
1191 | getExtendedHandshake :: Int -> S.Get ExtendedHandshake | ||
1192 | getExtendedHandshake messageSize | ||
1193 | | messageSize > maxEHandshakeSize | ||
1194 | = fail "extended handshake size exceeded limit" | ||
1195 | | otherwise = do | ||
1196 | bs <- getByteString messageSize | ||
1197 | either fail pure $ BE.decode bs | ||
1198 | |||
1199 | maxEUnknownSize :: Int | ||
1200 | maxEUnknownSize = 64 * 1024 | ||
1201 | |||
1202 | getExtendedUnknown :: Int -> S.Get BS.ByteString | ||
1203 | getExtendedUnknown len | ||
1204 | | len > maxEUnknownSize = fail "unknown extended message size exceeded limit" | ||
1205 | | otherwise = getByteString len | ||
1206 | |||
1207 | getExtendedMessage :: Int -> S.Get ExtendedMessage | ||
1208 | getExtendedMessage messageSize = do | ||
1209 | msgId <- getWord8 | ||
1210 | let msgBodySize = messageSize - 1 | ||
1211 | case msgId of | ||
1212 | 0 -> EHandshake <$> getExtendedHandshake msgBodySize | ||
1213 | 1 -> EMetadata msgId <$> getMetadata msgBodySize | ||
1214 | _ -> EUnknown msgId <$> getExtendedUnknown msgBodySize | ||
1215 | |||
1216 | -- | By spec. | ||
1217 | extendedMessageId :: MessageId | ||
1218 | extendedMessageId = 20 | ||
1219 | |||
1220 | putExt :: ExtendedMessageId -> BL.ByteString -> Put | ||
1221 | putExt mid lbs = do | ||
1222 | putWord32be $ fromIntegral (1 + 1 + BL.length lbs) | ||
1223 | putWord8 extendedMessageId | ||
1224 | putWord8 mid | ||
1225 | putLazyByteString lbs | ||
1226 | |||
1227 | -- NOTE: in contrast to getExtendedMessage this function put length | ||
1228 | -- and message id too! | ||
1229 | putExtendedMessage :: Putter ExtendedMessage | ||
1230 | putExtendedMessage (EHandshake hs) = putExt extHandshakeId $ BE.encode hs | ||
1231 | putExtendedMessage (EMetadata mid msg) = putExt mid $ putMetadata msg | ||
1232 | putExtendedMessage (EUnknown mid bs) = putExt mid $ BL.fromStrict bs | ||
diff --git a/bittorrent/src/Network/BitTorrent/Exchange/Session.hs b/bittorrent/src/Network/BitTorrent/Exchange/Session.hs new file mode 100644 index 00000000..38a3c3a6 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Exchange/Session.hs | |||
@@ -0,0 +1,586 @@ | |||
1 | {-# LANGUAGE CPP #-} | ||
2 | {-# LANGUAGE DeriveDataTypeable #-} | ||
3 | {-# LANGUAGE FlexibleInstances #-} | ||
4 | {-# LANGUAGE StandaloneDeriving #-} | ||
5 | {-# LANGUAGE TemplateHaskell #-} | ||
6 | {-# LANGUAGE TypeFamilies #-} | ||
7 | module Network.BitTorrent.Exchange.Session | ||
8 | ( -- * Session | ||
9 | Session | ||
10 | , Event (..) | ||
11 | , LogFun | ||
12 | , sessionLogger | ||
13 | |||
14 | -- * Construction | ||
15 | , newSession | ||
16 | , closeSession | ||
17 | , withSession | ||
18 | |||
19 | -- * Connection Set | ||
20 | , connect | ||
21 | , connectSink | ||
22 | , establish | ||
23 | |||
24 | -- * Query | ||
25 | , waitMetadata | ||
26 | , takeMetadata | ||
27 | ) where | ||
28 | |||
29 | import Control.Applicative | ||
30 | import Control.Concurrent | ||
31 | import Control.Concurrent.Chan.Split as CS | ||
32 | import Control.Concurrent.STM | ||
33 | import Control.Exception hiding (Handler) | ||
34 | import Control.Lens | ||
35 | import Control.Monad as M | ||
36 | import Control.Monad.Logger | ||
37 | import Control.Monad.Reader | ||
38 | import Data.ByteString as BS | ||
39 | import Data.ByteString.Lazy as BL | ||
40 | import Data.Conduit as C (Sink, awaitForever, (=$=), ($=)) | ||
41 | import qualified Data.Conduit as C | ||
42 | import Data.Conduit.List as C | ||
43 | import Data.Map as M | ||
44 | import Data.Monoid | ||
45 | import Data.Set as S | ||
46 | import Data.Text as T | ||
47 | import Data.Typeable | ||
48 | import Text.PrettyPrint hiding ((<>)) | ||
49 | import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) | ||
50 | import System.Log.FastLogger (LogStr, ToLogStr (..)) | ||
51 | |||
52 | import Data.BEncode as BE | ||
53 | import Data.Torrent as Torrent | ||
54 | import Network.BitTorrent.Internal.Types | ||
55 | import Network.Address | ||
56 | import Network.BitTorrent.Exchange.Bitfield as BF | ||
57 | import Network.BitTorrent.Exchange.Block as Block | ||
58 | import Network.BitTorrent.Exchange.Connection | ||
59 | import Network.BitTorrent.Exchange.Download as D | ||
60 | import Network.BitTorrent.Exchange.Message as Message | ||
61 | import System.Torrent.Storage | ||
62 | |||
63 | #if !MIN_VERSION_iproute(1,2,12) | ||
64 | deriving instance Ord IP | ||
65 | #endif | ||
66 | |||
67 | {----------------------------------------------------------------------- | ||
68 | -- Exceptions | ||
69 | -----------------------------------------------------------------------} | ||
70 | |||
71 | data ExchangeError | ||
72 | = InvalidRequest BlockIx StorageFailure | ||
73 | | CorruptedPiece PieceIx | ||
74 | deriving (Show, Typeable) | ||
75 | |||
76 | instance Exception ExchangeError | ||
77 | |||
78 | packException :: Exception e => (e -> ExchangeError) -> IO a -> IO a | ||
79 | packException f m = try m >>= either (throwIO . f) return | ||
80 | |||
81 | {----------------------------------------------------------------------- | ||
82 | -- Session state | ||
83 | -----------------------------------------------------------------------} | ||
84 | -- TODO unmap storage on zero connections | ||
85 | |||
86 | data Cached a = Cached | ||
87 | { cachedValue :: !a | ||
88 | , cachedData :: BL.ByteString -- keep lazy | ||
89 | } | ||
90 | |||
91 | cache :: BEncode a => a -> Cached a | ||
92 | cache s = Cached s (BE.encode s) | ||
93 | |||
94 | -- | Logger function. | ||
95 | type LogFun = Loc -> LogSource -> LogLevel -> LogStr -> IO () | ||
96 | |||
97 | --data SessionStatus = Seeder | Leecher | ||
98 | |||
99 | data SessionState | ||
100 | = WaitingMetadata | ||
101 | { metadataDownload :: MVar MetadataDownload | ||
102 | , metadataCompleted :: MVar InfoDict -- ^ used to unblock waiters | ||
103 | , contentRootPath :: FilePath | ||
104 | } | ||
105 | | HavingMetadata | ||
106 | { metadataCache :: Cached InfoDict | ||
107 | , contentDownload :: MVar ContentDownload | ||
108 | , contentStorage :: Storage | ||
109 | } | ||
110 | |||
111 | newSessionState :: FilePath -> Either InfoHash InfoDict -> IO SessionState | ||
112 | newSessionState rootPath (Left ih ) = do | ||
113 | WaitingMetadata <$> newMVar def <*> newEmptyMVar <*> pure rootPath | ||
114 | newSessionState rootPath (Right dict) = do | ||
115 | storage <- openInfoDict ReadWriteEx rootPath dict | ||
116 | download <- newMVar $ D.contentDownload (BF.haveNone (totalPieces storage)) | ||
117 | (piPieceLength (idPieceInfo dict)) | ||
118 | storage | ||
119 | return $ HavingMetadata (cache dict) download storage | ||
120 | |||
121 | closeSessionState :: SessionState -> IO () | ||
122 | closeSessionState WaitingMetadata {..} = return () | ||
123 | closeSessionState HavingMetadata {..} = close contentStorage | ||
124 | |||
125 | haveMetadata :: InfoDict -> SessionState -> IO SessionState | ||
126 | haveMetadata dict WaitingMetadata {..} = do | ||
127 | storage <- openInfoDict ReadWriteEx contentRootPath dict | ||
128 | download <- newMVar $ D.contentDownload (BF.haveNone (totalPieces storage)) | ||
129 | (piPieceLength (idPieceInfo dict)) | ||
130 | storage | ||
131 | return HavingMetadata | ||
132 | { metadataCache = cache dict | ||
133 | , contentDownload = download | ||
134 | , contentStorage = storage | ||
135 | } | ||
136 | haveMetadata _ s = return s | ||
137 | |||
138 | {----------------------------------------------------------------------- | ||
139 | -- Session | ||
140 | -----------------------------------------------------------------------} | ||
141 | |||
142 | data Session = Session | ||
143 | { sessionPeerId :: !(PeerId) | ||
144 | , sessionTopic :: !(InfoHash) | ||
145 | , sessionLogger :: !(LogFun) | ||
146 | , sessionEvents :: !(SendPort (Event Session)) | ||
147 | |||
148 | , sessionState :: !(MVar SessionState) | ||
149 | |||
150 | ------------------------------------------------------------------------ | ||
151 | , connectionsPrefs :: !ConnectionPrefs | ||
152 | |||
153 | -- | Connections either waiting for TCP/uTP 'connect' or waiting | ||
154 | -- for BT handshake. | ||
155 | , connectionsPending :: !(TVar (Set (PeerAddr IP))) | ||
156 | |||
157 | -- | Connections successfully handshaked and data transfer can | ||
158 | -- take place. | ||
159 | , connectionsEstablished :: !(TVar (Map (PeerAddr IP) (Connection Session))) | ||
160 | |||
161 | -- | TODO implement choking mechanism | ||
162 | , connectionsUnchoked :: [PeerAddr IP] | ||
163 | |||
164 | -- | Messages written to this channel will be sent to the all | ||
165 | -- connections, including pending connections (but right after | ||
166 | -- handshake). | ||
167 | , connectionsBroadcast :: !(Chan Message) | ||
168 | } | ||
169 | |||
170 | instance EventSource Session where | ||
171 | data Event Session | ||
172 | = ConnectingTo (PeerAddr IP) | ||
173 | | ConnectionEstablished (PeerAddr IP) | ||
174 | | ConnectionAborted | ||
175 | | ConnectionClosed (PeerAddr IP) | ||
176 | | SessionClosed | ||
177 | deriving Show | ||
178 | |||
179 | listen Session {..} = CS.listen sessionEvents | ||
180 | |||
181 | newSession :: LogFun | ||
182 | -> PeerAddr (Maybe IP) -- ^ /external/ address of this peer; | ||
183 | -> FilePath -- ^ root directory for content files; | ||
184 | -> Either InfoHash InfoDict -- ^ torrent info dictionary; | ||
185 | -> IO Session | ||
186 | newSession logFun addr rootPath source = do | ||
187 | let ih = either id idInfoHash source | ||
188 | pid <- maybe genPeerId return (peerId addr) | ||
189 | eventStream <- newSendPort | ||
190 | sState <- newSessionState rootPath source | ||
191 | sStateVar <- newMVar sState | ||
192 | pSetVar <- newTVarIO S.empty | ||
193 | eSetVar <- newTVarIO M.empty | ||
194 | chan <- newChan | ||
195 | return Session | ||
196 | { sessionPeerId = pid | ||
197 | , sessionTopic = ih | ||
198 | , sessionLogger = logFun | ||
199 | , sessionEvents = eventStream | ||
200 | , sessionState = sStateVar | ||
201 | , connectionsPrefs = def | ||
202 | , connectionsPending = pSetVar | ||
203 | , connectionsEstablished = eSetVar | ||
204 | , connectionsUnchoked = [] | ||
205 | , connectionsBroadcast = chan | ||
206 | } | ||
207 | |||
208 | closeSession :: Session -> IO () | ||
209 | closeSession Session {..} = do | ||
210 | s <- readMVar sessionState | ||
211 | closeSessionState s | ||
212 | {- | ||
213 | hSet <- atomically $ do | ||
214 | pSet <- swapTVar connectionsPending S.empty | ||
215 | eSet <- swapTVar connectionsEstablished S.empty | ||
216 | return pSet | ||
217 | mapM_ kill hSet | ||
218 | -} | ||
219 | |||
220 | withSession :: () | ||
221 | withSession = error "withSession" | ||
222 | |||
223 | {----------------------------------------------------------------------- | ||
224 | -- Logging | ||
225 | -----------------------------------------------------------------------} | ||
226 | |||
227 | instance MonadLogger (Connected Session) where | ||
228 | monadLoggerLog loc src lvl msg = do | ||
229 | conn <- ask | ||
230 | ses <- asks connSession | ||
231 | addr <- asks connRemoteAddr | ||
232 | let addrSrc = src <> " @ " <> T.pack (render (pPrint addr)) | ||
233 | liftIO $ sessionLogger ses loc addrSrc lvl (toLogStr msg) | ||
234 | |||
235 | logMessage :: MonadLogger m => Message -> m () | ||
236 | logMessage msg = logDebugN $ T.pack (render (pPrint msg)) | ||
237 | |||
238 | logEvent :: MonadLogger m => Text -> m () | ||
239 | logEvent = logInfoN | ||
240 | |||
241 | {----------------------------------------------------------------------- | ||
242 | -- Connection set | ||
243 | -----------------------------------------------------------------------} | ||
244 | --- Connection status transition: | ||
245 | --- | ||
246 | --- pending -> established -> finished -> closed | ||
247 | --- | \|/ /|\ | ||
248 | --- \-------------------------------------| | ||
249 | --- | ||
250 | --- Purpose of slots: | ||
251 | --- 1) to avoid duplicates | ||
252 | --- 2) connect concurrently | ||
253 | --- | ||
254 | |||
255 | -- | Add connection to the pending set. | ||
256 | pendingConnection :: PeerAddr IP -> Session -> STM Bool | ||
257 | pendingConnection addr Session {..} = do | ||
258 | pSet <- readTVar connectionsPending | ||
259 | eSet <- readTVar connectionsEstablished | ||
260 | if (addr `S.member` pSet) || (addr `M.member` eSet) | ||
261 | then return False | ||
262 | else do | ||
263 | modifyTVar' connectionsPending (S.insert addr) | ||
264 | return True | ||
265 | |||
266 | -- | Pending connection successfully established, add it to the | ||
267 | -- established set. | ||
268 | establishedConnection :: Connected Session () | ||
269 | establishedConnection = do | ||
270 | conn <- ask | ||
271 | addr <- asks connRemoteAddr | ||
272 | Session {..} <- asks connSession | ||
273 | liftIO $ atomically $ do | ||
274 | modifyTVar connectionsPending (S.delete addr) | ||
275 | modifyTVar connectionsEstablished (M.insert addr conn) | ||
276 | |||
277 | -- | Either this or remote peer decided to finish conversation | ||
278 | -- (conversation is alread /established/ connection), remote it from | ||
279 | -- the established set. | ||
280 | finishedConnection :: Connected Session () | ||
281 | finishedConnection = do | ||
282 | Session {..} <- asks connSession | ||
283 | addr <- asks connRemoteAddr | ||
284 | liftIO $ atomically $ do | ||
285 | modifyTVar connectionsEstablished $ M.delete addr | ||
286 | |||
287 | -- | There are no state for this connection, remove it from the all | ||
288 | -- sets. | ||
289 | closedConnection :: PeerAddr IP -> Session -> STM () | ||
290 | closedConnection addr Session {..} = do | ||
291 | modifyTVar connectionsPending $ S.delete addr | ||
292 | modifyTVar connectionsEstablished $ M.delete addr | ||
293 | |||
294 | getConnectionConfig :: Session -> IO (ConnectionConfig Session) | ||
295 | getConnectionConfig s @ Session {..} = do | ||
296 | chan <- dupChan connectionsBroadcast | ||
297 | let sessionLink = SessionLink { | ||
298 | linkTopic = sessionTopic | ||
299 | , linkPeerId = sessionPeerId | ||
300 | , linkMetadataSize = Nothing | ||
301 | , linkOutputChan = Just chan | ||
302 | , linkSession = s | ||
303 | } | ||
304 | return ConnectionConfig | ||
305 | { cfgPrefs = connectionsPrefs | ||
306 | , cfgSession = sessionLink | ||
307 | , cfgWire = mainWire | ||
308 | } | ||
309 | |||
310 | type Finalizer = IO () | ||
311 | type Runner = (ConnectionConfig Session -> IO ()) | ||
312 | |||
313 | runConnection :: Runner -> Finalizer -> PeerAddr IP -> Session -> IO () | ||
314 | runConnection runner finalize addr set @ Session {..} = do | ||
315 | _ <- forkIO (action `finally` cleanup) | ||
316 | return () | ||
317 | where | ||
318 | action = do | ||
319 | notExist <- atomically $ pendingConnection addr set | ||
320 | when notExist $ do | ||
321 | cfg <- getConnectionConfig set | ||
322 | runner cfg | ||
323 | |||
324 | cleanup = do | ||
325 | finalize | ||
326 | -- runStatusUpdates status (SS.resetPending addr) | ||
327 | -- TODO Metata.resetPending addr | ||
328 | atomically $ closedConnection addr set | ||
329 | |||
330 | -- | Establish connection from scratch. If this endpoint is already | ||
331 | -- connected, no new connections is created. This function do not block. | ||
332 | connect :: PeerAddr IP -> Session -> IO () | ||
333 | connect addr = runConnection (connectWire addr) (return ()) addr | ||
334 | |||
335 | -- | Establish connection with already pre-connected endpoint. If this | ||
336 | -- endpoint is already connected, no new connections is created. This | ||
337 | -- function do not block. | ||
338 | -- | ||
339 | -- 'PendingConnection' will be closed automatically, you do not need | ||
340 | -- to call 'closePending'. | ||
341 | establish :: PendingConnection -> Session -> IO () | ||
342 | establish conn = runConnection (acceptWire conn) (closePending conn) | ||
343 | (pendingPeer conn) | ||
344 | |||
345 | -- | Conduit version of 'connect'. | ||
346 | connectSink :: MonadIO m => Session -> Sink [PeerAddr IPv4] m () | ||
347 | connectSink s = C.mapM_ (liftIO . connectBatch) | ||
348 | where | ||
349 | connectBatch = M.mapM_ (\ addr -> connect (IPv4 <$> addr) s) | ||
350 | |||
351 | -- | Why do we need this message? | ||
352 | type BroadcastMessage = ExtendedCaps -> Message | ||
353 | |||
354 | broadcast :: BroadcastMessage -> Session -> IO () | ||
355 | broadcast = error "broadcast" | ||
356 | |||
357 | {----------------------------------------------------------------------- | ||
358 | -- Helpers | ||
359 | -----------------------------------------------------------------------} | ||
360 | |||
361 | waitMVar :: MVar a -> IO () | ||
362 | waitMVar m = withMVar m (const (return ())) | ||
363 | |||
364 | -- This function appear in new GHC "out of box". (moreover it is atomic) | ||
365 | tryReadMVar :: MVar a -> IO (Maybe a) | ||
366 | tryReadMVar m = do | ||
367 | ma <- tryTakeMVar m | ||
368 | maybe (return ()) (putMVar m) ma | ||
369 | return ma | ||
370 | |||
371 | readBlock :: BlockIx -> Storage -> IO (Block BL.ByteString) | ||
372 | readBlock bix @ BlockIx {..} s = do | ||
373 | p <- packException (InvalidRequest bix) $ do readPiece ixPiece s | ||
374 | let chunk = BL.take (fromIntegral ixLength) $ | ||
375 | BL.drop (fromIntegral ixOffset) (pieceData p) | ||
376 | if BL.length chunk == fromIntegral ixLength | ||
377 | then return $ Block ixPiece ixOffset chunk | ||
378 | else throwIO $ InvalidRequest bix (InvalidSize ixLength) | ||
379 | |||
380 | -- | | ||
381 | tryReadMetadataBlock :: PieceIx | ||
382 | -> Connected Session (Maybe (Torrent.Piece BS.ByteString, Int)) | ||
383 | tryReadMetadataBlock pix = do | ||
384 | Session {..} <- asks connSession | ||
385 | s <- liftIO (readMVar sessionState) | ||
386 | case s of | ||
387 | WaitingMetadata {..} -> error "tryReadMetadataBlock" | ||
388 | HavingMetadata {..} -> error "tryReadMetadataBlock" | ||
389 | |||
390 | sendBroadcast :: PeerMessage msg => msg -> Wire Session () | ||
391 | sendBroadcast msg = do | ||
392 | Session {..} <- asks connSession | ||
393 | error "sendBroadcast" | ||
394 | -- liftIO $ msg `broadcast` sessionConnections | ||
395 | |||
396 | waitMetadata :: Session -> IO InfoDict | ||
397 | waitMetadata Session {..} = do | ||
398 | s <- readMVar sessionState | ||
399 | case s of | ||
400 | WaitingMetadata {..} -> readMVar metadataCompleted | ||
401 | HavingMetadata {..} -> return (cachedValue metadataCache) | ||
402 | |||
403 | takeMetadata :: Session -> IO (Maybe InfoDict) | ||
404 | takeMetadata Session {..} = do | ||
405 | s <- readMVar sessionState | ||
406 | case s of | ||
407 | WaitingMetadata {..} -> return Nothing | ||
408 | HavingMetadata {..} -> return (Just (cachedValue metadataCache)) | ||
409 | |||
410 | {----------------------------------------------------------------------- | ||
411 | -- Triggers | ||
412 | -----------------------------------------------------------------------} | ||
413 | |||
414 | -- | Trigger is the reaction of a handler at some event. | ||
415 | type Trigger = Wire Session () | ||
416 | |||
417 | interesting :: Trigger | ||
418 | interesting = do | ||
419 | addr <- asks connRemoteAddr | ||
420 | sendMessage (Interested True) | ||
421 | sendMessage (Choking False) | ||
422 | tryFillRequestQueue | ||
423 | |||
424 | fillRequestQueue :: Trigger | ||
425 | fillRequestQueue = do | ||
426 | maxN <- lift getMaxQueueLength | ||
427 | rbf <- use connBitfield | ||
428 | addr <- asks connRemoteAddr | ||
429 | -- blks <- withStatusUpdates $ do | ||
430 | -- n <- getRequestQueueLength addr | ||
431 | -- scheduleBlocks addr rbf (maxN - n) | ||
432 | -- mapM_ (sendMessage . Request) blks | ||
433 | return () | ||
434 | |||
435 | tryFillRequestQueue :: Trigger | ||
436 | tryFillRequestQueue = do | ||
437 | allowed <- canDownload <$> use connStatus | ||
438 | when allowed $ do | ||
439 | fillRequestQueue | ||
440 | |||
441 | {----------------------------------------------------------------------- | ||
442 | -- Incoming message handling | ||
443 | -----------------------------------------------------------------------} | ||
444 | |||
445 | type Handler msg = msg -> Wire Session () | ||
446 | |||
447 | handleStatus :: Handler StatusUpdate | ||
448 | handleStatus s = do | ||
449 | connStatus %= over remoteStatus (updateStatus s) | ||
450 | case s of | ||
451 | Interested _ -> return () | ||
452 | Choking True -> do | ||
453 | addr <- asks connRemoteAddr | ||
454 | -- withStatusUpdates (SS.resetPending addr) | ||
455 | return () | ||
456 | Choking False -> tryFillRequestQueue | ||
457 | |||
458 | handleAvailable :: Handler Available | ||
459 | handleAvailable msg = do | ||
460 | connBitfield %= case msg of | ||
461 | Have ix -> BF.insert ix | ||
462 | Bitfield bf -> const bf | ||
463 | |||
464 | --thisBf <- getThisBitfield | ||
465 | thisBf <- undefined | ||
466 | case msg of | ||
467 | Have ix | ||
468 | | ix `BF.member` thisBf -> return () | ||
469 | | otherwise -> interesting | ||
470 | Bitfield bf | ||
471 | | bf `BF.isSubsetOf` thisBf -> return () | ||
472 | | otherwise -> interesting | ||
473 | |||
474 | handleTransfer :: Handler Transfer | ||
475 | handleTransfer (Request bix) = do | ||
476 | Session {..} <- asks connSession | ||
477 | s <- liftIO $ readMVar sessionState | ||
478 | case s of | ||
479 | WaitingMetadata {..} -> return () | ||
480 | HavingMetadata {..} -> do | ||
481 | bitfield <- undefined -- getThisBitfield | ||
482 | upload <- canUpload <$> use connStatus | ||
483 | when (upload && ixPiece bix `BF.member` bitfield) $ do | ||
484 | blk <- liftIO $ readBlock bix contentStorage | ||
485 | sendMessage (Message.Piece blk) | ||
486 | |||
487 | handleTransfer (Message.Piece blk) = do | ||
488 | Session {..} <- asks connSession | ||
489 | s <- liftIO $ readMVar sessionState | ||
490 | case s of | ||
491 | WaitingMetadata {..} -> return () -- TODO (?) break connection | ||
492 | HavingMetadata {..} -> do | ||
493 | isSuccess <- undefined -- withStatusUpdates (SS.pushBlock blk storage) | ||
494 | case isSuccess of | ||
495 | Nothing -> liftIO $ throwIO $ userError "block is not requested" | ||
496 | Just isCompleted -> do | ||
497 | when isCompleted $ do | ||
498 | sendBroadcast (Have (blkPiece blk)) | ||
499 | -- maybe send not interested | ||
500 | tryFillRequestQueue | ||
501 | |||
502 | handleTransfer (Cancel bix) = filterQueue (not . (transferResponse bix)) | ||
503 | where | ||
504 | transferResponse bix (Transfer (Message.Piece blk)) = blockIx blk == bix | ||
505 | transferResponse _ _ = False | ||
506 | |||
507 | {----------------------------------------------------------------------- | ||
508 | -- Metadata exchange | ||
509 | -----------------------------------------------------------------------} | ||
510 | -- TODO introduce new metadata exchange specific exceptions | ||
511 | |||
512 | waitForMetadata :: Trigger | ||
513 | waitForMetadata = do | ||
514 | Session {..} <- asks connSession | ||
515 | needFetch <- undefined --liftIO (isEmptyMVar infodict) | ||
516 | when needFetch $ do | ||
517 | canFetch <- allowed ExtMetadata <$> use connExtCaps | ||
518 | if canFetch | ||
519 | then tryRequestMetadataBlock | ||
520 | else undefined -- liftIO (waitMVar infodict) | ||
521 | |||
522 | tryRequestMetadataBlock :: Trigger | ||
523 | tryRequestMetadataBlock = do | ||
524 | mpix <- lift $ undefined --withMetadataUpdates Metadata.scheduleBlock | ||
525 | case mpix of | ||
526 | Nothing -> error "tryRequestMetadataBlock" | ||
527 | Just pix -> sendMessage (MetadataRequest pix) | ||
528 | |||
529 | handleMetadata :: Handler ExtendedMetadata | ||
530 | handleMetadata (MetadataRequest pix) = | ||
531 | lift (tryReadMetadataBlock pix) >>= sendMessage . mkResponse | ||
532 | where | ||
533 | mkResponse Nothing = MetadataReject pix | ||
534 | mkResponse (Just (piece, total)) = MetadataData piece total | ||
535 | |||
536 | handleMetadata (MetadataData {..}) = do | ||
537 | ih <- asks connTopic | ||
538 | mdict <- lift $ undefined --withMetadataUpdates (Metadata.pushBlock piece ih) | ||
539 | case mdict of | ||
540 | Nothing -> tryRequestMetadataBlock -- not completed, need all blocks | ||
541 | Just dict -> do -- complete, wake up payload fetch | ||
542 | Session {..} <- asks connSession | ||
543 | liftIO $ modifyMVar_ sessionState (haveMetadata dict) | ||
544 | |||
545 | handleMetadata (MetadataReject pix) = do | ||
546 | lift $ undefined -- withMetadataUpdates (Metadata.cancelPending pix) | ||
547 | |||
548 | handleMetadata (MetadataUnknown _ ) = do | ||
549 | logInfoN "Unknown metadata message" | ||
550 | |||
551 | {----------------------------------------------------------------------- | ||
552 | -- Main entry point | ||
553 | -----------------------------------------------------------------------} | ||
554 | |||
555 | acceptRehandshake :: ExtendedHandshake -> Trigger | ||
556 | acceptRehandshake ehs = error "acceptRehandshake" | ||
557 | |||
558 | handleExtended :: Handler ExtendedMessage | ||
559 | handleExtended (EHandshake ehs) = acceptRehandshake ehs | ||
560 | handleExtended (EMetadata _ msg) = handleMetadata msg | ||
561 | handleExtended (EUnknown _ _ ) = logWarnN "Unknown extension message" | ||
562 | |||
563 | handleMessage :: Handler Message | ||
564 | handleMessage KeepAlive = return () | ||
565 | handleMessage (Status s) = handleStatus s | ||
566 | handleMessage (Available msg) = handleAvailable msg | ||
567 | handleMessage (Transfer msg) = handleTransfer msg | ||
568 | handleMessage (Port n) = error "handleMessage" | ||
569 | handleMessage (Fast _) = error "handleMessage" | ||
570 | handleMessage (Extended msg) = handleExtended msg | ||
571 | |||
572 | exchange :: Wire Session () | ||
573 | exchange = do | ||
574 | waitForMetadata | ||
575 | bf <- undefined --getThisBitfield | ||
576 | sendMessage (Bitfield bf) | ||
577 | awaitForever handleMessage | ||
578 | |||
579 | mainWire :: Wire Session () | ||
580 | mainWire = do | ||
581 | lift establishedConnection | ||
582 | Session {..} <- asks connSession | ||
583 | -- lift $ resizeBitfield (totalPieces storage) | ||
584 | logEvent "Connection established" | ||
585 | iterM logMessage =$= exchange =$= iterM logMessage | ||
586 | lift finishedConnection | ||
diff --git a/bittorrent/src/Network/BitTorrent/Internal/Cache.hs b/bittorrent/src/Network/BitTorrent/Internal/Cache.hs new file mode 100644 index 00000000..8c74467a --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Internal/Cache.hs | |||
@@ -0,0 +1,169 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2014 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Cached data for tracker responses. | ||
9 | -- | ||
10 | module Network.BitTorrent.Internal.Cache | ||
11 | ( -- * Cache | ||
12 | Cached | ||
13 | , lastUpdated | ||
14 | , updateInterval | ||
15 | , minUpdateInterval | ||
16 | |||
17 | -- * Construction | ||
18 | , newCached | ||
19 | , newCached_ | ||
20 | |||
21 | -- * Query | ||
22 | , isAlive | ||
23 | , isStalled | ||
24 | , isExpired | ||
25 | , canUpdate | ||
26 | , shouldUpdate | ||
27 | |||
28 | -- * Cached data | ||
29 | , tryTakeData | ||
30 | , unsafeTryTakeData | ||
31 | , takeData | ||
32 | ) where | ||
33 | |||
34 | import Control.Applicative | ||
35 | import Data.Monoid | ||
36 | import Data.Default | ||
37 | import Data.Time | ||
38 | import Data.Time.Clock.POSIX | ||
39 | import System.IO.Unsafe | ||
40 | |||
41 | |||
42 | data Cached a = Cached | ||
43 | { -- | Time of resource creation. | ||
44 | lastUpdated :: !POSIXTime | ||
45 | |||
46 | -- | Minimum invalidation timeout. | ||
47 | , minUpdateInterval :: !NominalDiffTime | ||
48 | |||
49 | -- | Resource lifetime. | ||
50 | , updateInterval :: !NominalDiffTime | ||
51 | |||
52 | -- | Resource data. | ||
53 | , cachedData :: a | ||
54 | } deriving (Show, Eq) | ||
55 | |||
56 | -- INVARIANT: minUpdateInterval <= updateInterval | ||
57 | |||
58 | instance Default (Cached a) where | ||
59 | def = mempty | ||
60 | |||
61 | instance Functor Cached where | ||
62 | fmap f (Cached t i m a) = Cached t i m (f a) | ||
63 | |||
64 | posixEpoch :: NominalDiffTime | ||
65 | posixEpoch = 1000000000000000000000000000000000000000000000000000000 | ||
66 | |||
67 | instance Applicative Cached where | ||
68 | pure = Cached 0 posixEpoch posixEpoch | ||
69 | f <*> c = Cached | ||
70 | { lastUpdated = undefined | ||
71 | , minUpdateInterval = undefined | ||
72 | , updateInterval = undefined | ||
73 | , cachedData = cachedData f (cachedData c) | ||
74 | } | ||
75 | |||
76 | instance Alternative Cached where | ||
77 | empty = mempty | ||
78 | (<|>) = error "cached alternative instance: not implemented" | ||
79 | |||
80 | instance Monad Cached where | ||
81 | return = pure | ||
82 | Cached {..} >>= f = Cached | ||
83 | { lastUpdated = undefined | ||
84 | , updateInterval = undefined | ||
85 | , minUpdateInterval = undefined | ||
86 | , cachedData = undefined | ||
87 | } | ||
88 | |||
89 | instance Monoid (Cached a) where | ||
90 | mempty = Cached | ||
91 | { lastUpdated = 0 | ||
92 | , minUpdateInterval = 0 | ||
93 | , updateInterval = 0 | ||
94 | , cachedData = error "cached mempty: impossible happen" | ||
95 | } | ||
96 | |||
97 | mappend a b | ||
98 | | expirationTime a > expirationTime b = a | ||
99 | | otherwise = b | ||
100 | |||
101 | normalize :: NominalDiffTime -> NominalDiffTime | ||
102 | -> (NominalDiffTime, NominalDiffTime) | ||
103 | normalize a b | ||
104 | | a < b = (a, b) | ||
105 | | otherwise = (b, a) | ||
106 | {-# INLINE normalize #-} | ||
107 | |||
108 | newCached :: NominalDiffTime -> NominalDiffTime -> a -> IO (Cached a) | ||
109 | newCached minInterval interval x = do | ||
110 | t <- getPOSIXTime | ||
111 | let (mui, ui) = normalize minInterval interval | ||
112 | return Cached | ||
113 | { lastUpdated = t | ||
114 | , minUpdateInterval = mui | ||
115 | , updateInterval = ui | ||
116 | , cachedData = x | ||
117 | } | ||
118 | |||
119 | newCached_ :: NominalDiffTime -> a -> IO (Cached a) | ||
120 | newCached_ interval x = newCached interval interval x | ||
121 | {-# INLINE newCached_ #-} | ||
122 | |||
123 | expirationTime :: Cached a -> POSIXTime | ||
124 | expirationTime Cached {..} = undefined | ||
125 | |||
126 | isAlive :: Cached a -> IO Bool | ||
127 | isAlive Cached {..} = do | ||
128 | currentTime <- getPOSIXTime | ||
129 | return $ lastUpdated + updateInterval > currentTime | ||
130 | |||
131 | isExpired :: Cached a -> IO Bool | ||
132 | isExpired Cached {..} = undefined | ||
133 | |||
134 | isStalled :: Cached a -> IO Bool | ||
135 | isStalled Cached {..} = undefined | ||
136 | |||
137 | canUpdate :: Cached a -> IO (Maybe NominalDiffTime) | ||
138 | canUpdate = undefined --isStaled | ||
139 | |||
140 | shouldUpdate :: Cached a -> IO (Maybe NominalDiffTime) | ||
141 | shouldUpdate = undefined -- isExpired | ||
142 | |||
143 | tryTakeData :: Cached a -> IO (Maybe a) | ||
144 | tryTakeData c = do | ||
145 | alive <- isAlive c | ||
146 | return $ if alive then Just (cachedData c) else Nothing | ||
147 | |||
148 | unsafeTryTakeData :: Cached a -> Maybe a | ||
149 | unsafeTryTakeData = unsafePerformIO . tryTakeData | ||
150 | |||
151 | invalidateData :: Cached a -> IO a -> IO (Cached a) | ||
152 | invalidateData Cached {..} action = do | ||
153 | t <- getPOSIXTime | ||
154 | x <- action | ||
155 | return Cached | ||
156 | { lastUpdated = t | ||
157 | , updateInterval = updateInterval | ||
158 | , minUpdateInterval = minUpdateInterval | ||
159 | , cachedData = x | ||
160 | } | ||
161 | |||
162 | takeData :: Cached a -> IO a -> IO a | ||
163 | takeData c action = do | ||
164 | mdata <- tryTakeData c | ||
165 | case mdata of | ||
166 | Just a -> return a | ||
167 | Nothing -> do | ||
168 | c' <- invalidateData c action | ||
169 | takeData c' action | ||
diff --git a/bittorrent/src/Network/BitTorrent/Internal/Progress.hs b/bittorrent/src/Network/BitTorrent/Internal/Progress.hs new file mode 100644 index 00000000..6ac889e2 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Internal/Progress.hs | |||
@@ -0,0 +1,154 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- 'Progress' used to track amount downloaded\/left\/upload bytes | ||
9 | -- either on per client or per torrent basis. This value is used to | ||
10 | -- notify the tracker and usually shown to the user. To aggregate | ||
11 | -- total progress you can use the Monoid instance. | ||
12 | -- | ||
13 | {-# LANGUAGE TemplateHaskell #-} | ||
14 | {-# LANGUAGE ViewPatterns #-} | ||
15 | {-# OPTIONS -fno-warn-orphans #-} | ||
16 | module Network.BitTorrent.Internal.Progress | ||
17 | ( -- * Progress | ||
18 | Progress (..) | ||
19 | |||
20 | -- * Lens | ||
21 | , left | ||
22 | , uploaded | ||
23 | , downloaded | ||
24 | |||
25 | -- * Construction | ||
26 | , startProgress | ||
27 | , downloadedProgress | ||
28 | , enqueuedProgress | ||
29 | , uploadedProgress | ||
30 | , dequeuedProgress | ||
31 | |||
32 | -- * Query | ||
33 | , canDownload | ||
34 | , canUpload | ||
35 | ) where | ||
36 | |||
37 | import Control.Applicative | ||
38 | import Control.Lens hiding ((%=)) | ||
39 | import Data.ByteString.Lazy.Builder as BS | ||
40 | import Data.ByteString.Lazy.Builder.ASCII as BS | ||
41 | import Data.Default | ||
42 | import Data.Monoid | ||
43 | import Data.Serialize as S | ||
44 | import Data.Ratio | ||
45 | import Data.Word | ||
46 | import Network.HTTP.Types.QueryLike | ||
47 | import Text.PrettyPrint as PP | ||
48 | import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) | ||
49 | |||
50 | |||
51 | -- | Progress data is considered as dynamic within one client | ||
52 | -- session. This data also should be shared across client application | ||
53 | -- sessions (e.g. files), otherwise use 'startProgress' to get initial | ||
54 | -- 'Progress' value. | ||
55 | -- | ||
56 | data Progress = Progress | ||
57 | { _downloaded :: {-# UNPACK #-} !Word64 -- ^ Total amount of bytes downloaded; | ||
58 | , _left :: {-# UNPACK #-} !Word64 -- ^ Total amount of bytes left; | ||
59 | , _uploaded :: {-# UNPACK #-} !Word64 -- ^ Total amount of bytes uploaded. | ||
60 | } deriving (Show, Read, Eq) | ||
61 | |||
62 | $(makeLenses ''Progress) | ||
63 | |||
64 | -- | UDP tracker compatible encoding. | ||
65 | instance Serialize Progress where | ||
66 | put Progress {..} = do | ||
67 | putWord64be $ fromIntegral _downloaded | ||
68 | putWord64be $ fromIntegral _left | ||
69 | putWord64be $ fromIntegral _uploaded | ||
70 | |||
71 | get = Progress | ||
72 | <$> (fromIntegral <$> getWord64be) | ||
73 | <*> (fromIntegral <$> getWord64be) | ||
74 | <*> (fromIntegral <$> getWord64be) | ||
75 | |||
76 | instance Default Progress where | ||
77 | def = Progress 0 0 0 | ||
78 | {-# INLINE def #-} | ||
79 | |||
80 | -- | Can be used to aggregate total progress. | ||
81 | instance Monoid Progress where | ||
82 | mempty = def | ||
83 | {-# INLINE mempty #-} | ||
84 | |||
85 | mappend (Progress da la ua) (Progress db lb ub) = Progress | ||
86 | { _downloaded = da + db | ||
87 | , _left = la + lb | ||
88 | , _uploaded = ua + ub | ||
89 | } | ||
90 | {-# INLINE mappend #-} | ||
91 | |||
92 | instance QueryValueLike Builder where | ||
93 | toQueryValue = toQueryValue . BS.toLazyByteString | ||
94 | |||
95 | instance QueryValueLike Word64 where | ||
96 | toQueryValue = toQueryValue . BS.word64Dec | ||
97 | |||
98 | -- | HTTP Tracker protocol compatible encoding. | ||
99 | instance QueryLike Progress where | ||
100 | toQuery Progress {..} = | ||
101 | [ ("uploaded" , toQueryValue _uploaded) | ||
102 | , ("left" , toQueryValue _left) | ||
103 | , ("downloaded", toQueryValue _downloaded) | ||
104 | ] | ||
105 | |||
106 | instance Pretty Progress where | ||
107 | pPrint Progress {..} = | ||
108 | "/\\" <+> PP.text (show _uploaded) $$ | ||
109 | "\\/" <+> PP.text (show _downloaded) $$ | ||
110 | "left" <+> PP.text (show _left) | ||
111 | |||
112 | -- | Initial progress is used when there are no session before. | ||
113 | -- | ||
114 | -- Please note that tracker might penalize client some way if the do | ||
115 | -- not accumulate progress. If possible and save 'Progress' between | ||
116 | -- client sessions to avoid that. | ||
117 | -- | ||
118 | startProgress :: Integer -> Progress | ||
119 | startProgress = Progress 0 0 . fromIntegral | ||
120 | {-# INLINE startProgress #-} | ||
121 | |||
122 | -- | Used when the client download some data from /any/ peer. | ||
123 | downloadedProgress :: Int -> Progress -> Progress | ||
124 | downloadedProgress (fromIntegral -> amount) | ||
125 | = (left -~ amount) | ||
126 | . (downloaded +~ amount) | ||
127 | {-# INLINE downloadedProgress #-} | ||
128 | |||
129 | -- | Used when the client upload some data to /any/ peer. | ||
130 | uploadedProgress :: Int -> Progress -> Progress | ||
131 | uploadedProgress (fromIntegral -> amount) = uploaded +~ amount | ||
132 | {-# INLINE uploadedProgress #-} | ||
133 | |||
134 | -- | Used when leecher join client session. | ||
135 | enqueuedProgress :: Integer -> Progress -> Progress | ||
136 | enqueuedProgress amount = left +~ fromIntegral amount | ||
137 | {-# INLINE enqueuedProgress #-} | ||
138 | |||
139 | -- | Used when leecher leave client session. | ||
140 | -- (e.g. user deletes not completed torrent) | ||
141 | dequeuedProgress :: Integer -> Progress -> Progress | ||
142 | dequeuedProgress amount = left -~ fromIntegral amount | ||
143 | {-# INLINE dequeuedProgress #-} | ||
144 | |||
145 | ri2rw64 :: Ratio Int -> Ratio Word64 | ||
146 | ri2rw64 x = fromIntegral (numerator x) % fromIntegral (denominator x) | ||
147 | |||
148 | -- | Check global /download/ limit by uploaded \/ downloaded ratio. | ||
149 | canDownload :: Ratio Int -> Progress -> Bool | ||
150 | canDownload limit Progress {..} = _uploaded % _downloaded > ri2rw64 limit | ||
151 | |||
152 | -- | Check global /upload/ limit by downloaded \/ uploaded ratio. | ||
153 | canUpload :: Ratio Int -> Progress -> Bool | ||
154 | canUpload limit Progress {..} = _downloaded % _uploaded > ri2rw64 limit | ||
diff --git a/bittorrent/src/Network/BitTorrent/Internal/Types.hs b/bittorrent/src/Network/BitTorrent/Internal/Types.hs new file mode 100644 index 00000000..d157db3e --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Internal/Types.hs | |||
@@ -0,0 +1,10 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | module Network.BitTorrent.Internal.Types | ||
3 | ( EventSource (..) | ||
4 | ) where | ||
5 | |||
6 | import Control.Concurrent.Chan.Split | ||
7 | |||
8 | class EventSource source where | ||
9 | data Event source | ||
10 | listen :: source -> IO (ReceivePort (Event source)) | ||
diff --git a/bittorrent/src/Network/BitTorrent/Readme.md b/bittorrent/src/Network/BitTorrent/Readme.md new file mode 100644 index 00000000..ebf9545e --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Readme.md | |||
@@ -0,0 +1,10 @@ | |||
1 | Layout | ||
2 | ====== | ||
3 | |||
4 | | module group | can import | main purpose | | ||
5 | |:-------------|:------------:|:--------------------------------------:| | ||
6 | | Core | | common datatypes | | ||
7 | | DHT | Core | centralized peer discovery | | ||
8 | | Tracker | Core | decentralized peer discovery | | ||
9 | | Exchange | Core | torrent content exchange | | ||
10 | | Client | any other | core of bittorrent client application | | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker.hs b/bittorrent/src/Network/BitTorrent/Tracker.hs new file mode 100644 index 00000000..6db67559 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker.hs | |||
@@ -0,0 +1,50 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : non-portable | ||
7 | -- | ||
8 | -- This module provides high level API for peer -> tracker | ||
9 | -- communication. Tracker is used to discover other peers in the | ||
10 | -- network using torrent info hash. | ||
11 | -- | ||
12 | {-# LANGUAGE TemplateHaskell #-} | ||
13 | module Network.BitTorrent.Tracker | ||
14 | ( -- * RPC Manager | ||
15 | PeerInfo (..) | ||
16 | , Options | ||
17 | , Manager | ||
18 | , newManager | ||
19 | , closeManager | ||
20 | , withManager | ||
21 | |||
22 | -- * Multitracker session | ||
23 | , trackerList | ||
24 | , Session | ||
25 | , Event (..) | ||
26 | , newSession | ||
27 | , closeSession | ||
28 | , withSession | ||
29 | |||
30 | -- ** Events | ||
31 | , AnnounceEvent (..) | ||
32 | , notify | ||
33 | , askPeers | ||
34 | |||
35 | -- ** Session state | ||
36 | , TrackerSession | ||
37 | , trackerPeers | ||
38 | , trackerScrape | ||
39 | |||
40 | , tryTakeData | ||
41 | , unsafeTryTakeData | ||
42 | |||
43 | , getSessionState | ||
44 | ) where | ||
45 | |||
46 | import Network.BitTorrent.Internal.Cache (tryTakeData, unsafeTryTakeData) | ||
47 | import Network.BitTorrent.Tracker.Message | ||
48 | import Network.BitTorrent.Tracker.List | ||
49 | import Network.BitTorrent.Tracker.RPC | ||
50 | import Network.BitTorrent.Tracker.Session | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/List.hs b/bittorrent/src/Network/BitTorrent/Tracker/List.hs new file mode 100644 index 00000000..0eb11641 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/List.hs | |||
@@ -0,0 +1,193 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2014 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Multitracker Metadata Extension support. | ||
9 | -- | ||
10 | -- For more info see: <http://www.bittorrent.org/beps/bep_0012.html> | ||
11 | -- | ||
12 | {-# LANGUAGE FlexibleInstances #-} | ||
13 | module Network.BitTorrent.Tracker.List | ||
14 | ( -- * Tracker list | ||
15 | TierEntry | ||
16 | , TrackerList | ||
17 | |||
18 | -- * Construction | ||
19 | , trackerList | ||
20 | , shuffleTiers | ||
21 | , mapWithURI | ||
22 | , Network.BitTorrent.Tracker.List.toList | ||
23 | |||
24 | -- * Traversals | ||
25 | , traverseAll | ||
26 | , traverseTiers | ||
27 | ) where | ||
28 | |||
29 | import Prelude hiding (mapM, foldr) | ||
30 | import Control.Arrow | ||
31 | import Control.Applicative | ||
32 | import Control.Exception | ||
33 | import Data.Default | ||
34 | import Data.List as L (map, elem, any, filter, null) | ||
35 | import Data.Maybe | ||
36 | import Data.Foldable | ||
37 | import Data.Traversable | ||
38 | import Network.URI | ||
39 | import System.Random.Shuffle | ||
40 | |||
41 | import Data.Torrent | ||
42 | import Network.BitTorrent.Tracker.RPC as RPC | ||
43 | |||
44 | {----------------------------------------------------------------------- | ||
45 | -- Tracker list datatype | ||
46 | -----------------------------------------------------------------------} | ||
47 | |||
48 | type TierEntry a = (URI, a) | ||
49 | type Tier a = [TierEntry a] | ||
50 | |||
51 | -- | Tracker list is either a single tracker or list of tiers. All | ||
52 | -- trackers in each tier must be checked before the client goes on to | ||
53 | -- the next tier. | ||
54 | data TrackerList a | ||
55 | = Announce (TierEntry a) -- ^ torrent file 'announce' field only | ||
56 | | TierList [Tier a] -- ^ torrent file 'announce-list' field only | ||
57 | deriving (Show, Eq) | ||
58 | |||
59 | -- | Empty tracker list. Can be used for trackerless torrents. | ||
60 | instance Default (TrackerList a) where | ||
61 | def = TierList [] | ||
62 | |||
63 | instance Functor TrackerList where | ||
64 | fmap f (Announce (uri, a)) = Announce (uri, f a) | ||
65 | fmap f (TierList a) = TierList (fmap (fmap (second f)) a) | ||
66 | |||
67 | instance Foldable TrackerList where | ||
68 | foldr f z (Announce e ) = f (snd e) z | ||
69 | foldr f z (TierList xs) = foldr (flip (foldr (f . snd))) z xs | ||
70 | |||
71 | _traverseEntry f (uri, a) = (,) uri <$> f a | ||
72 | |||
73 | instance Traversable TrackerList where | ||
74 | traverse f (Announce e ) = Announce <$> _traverseEntry f e | ||
75 | traverse f (TierList xs) = | ||
76 | TierList <$> traverse (traverse (_traverseEntry f)) xs | ||
77 | |||
78 | traverseWithURI :: Applicative f | ||
79 | => (TierEntry a -> f b) -> TrackerList a -> f (TrackerList b) | ||
80 | traverseWithURI f (Announce (uri, a)) = (Announce . (,) uri) <$> f (uri, a) | ||
81 | traverseWithURI f (TierList xxs ) = | ||
82 | TierList <$> traverse (traverse (traverseEntry f)) xxs | ||
83 | where | ||
84 | traverseEntry f (uri, a) = (,) uri <$> f (uri, a) | ||
85 | |||
86 | {----------------------------------------------------------------------- | ||
87 | -- List extraction | ||
88 | -----------------------------------------------------------------------} | ||
89 | -- BEP12 do not expose any restrictions for the content of | ||
90 | -- 'announce-list' key - there are some /bad/ cases can happen with | ||
91 | -- poorly designed or even malicious torrent creation software. | ||
92 | -- | ||
93 | -- Bad case #1: announce-list is present, but empty. | ||
94 | -- | ||
95 | -- { tAnnounce = Just "http://a.com" | ||
96 | -- , tAnnounceList = Just [[]] | ||
97 | -- } | ||
98 | -- | ||
99 | -- Bad case #2: announce uri do not present in announce list. | ||
100 | -- | ||
101 | -- { tAnnounce = Just "http://a.com" | ||
102 | -- , tAnnounceList = Just [["udp://a.com"]] | ||
103 | -- } | ||
104 | -- | ||
105 | -- The addBackup function solves both problems by adding announce uri | ||
106 | -- as backup tier. | ||
107 | -- | ||
108 | addBackup :: [[URI]] -> URI -> [[URI]] | ||
109 | addBackup tiers bkp | ||
110 | | L.any (L.elem bkp) tiers = tiers | ||
111 | | otherwise = tiers ++ [[bkp]] | ||
112 | |||
113 | fixList :: Maybe [[URI]] -> Maybe URI -> Maybe [[URI]] | ||
114 | fixList mxss mx = do | ||
115 | xss <- mxss | ||
116 | let xss' = L.filter (not . L.null) xss | ||
117 | return $ maybe xss' (addBackup xss') mx | ||
118 | |||
119 | -- | Extract set of trackers from torrent file. The 'tAnnounce' key is | ||
120 | -- only ignored if the 'tAnnounceList' key is present. | ||
121 | trackerList :: Torrent -> TrackerList () | ||
122 | trackerList Torrent {..} = fromMaybe (TierList []) $ do | ||
123 | (TierList . tierList) <$> (tAnnounceList `fixList` tAnnounce) | ||
124 | <|> (Announce . nullEntry) <$> tAnnounce | ||
125 | where | ||
126 | nullEntry uri = (uri, ()) | ||
127 | tierList = L.map (L.map nullEntry) | ||
128 | |||
129 | -- | Shuffle /order of trackers/ in each tier, preserving original | ||
130 | -- /order of tiers/. This can help to balance the load between the | ||
131 | -- trackers. | ||
132 | shuffleTiers :: TrackerList a -> IO (TrackerList a) | ||
133 | shuffleTiers (Announce a ) = return (Announce a) | ||
134 | shuffleTiers (TierList xs) = TierList <$> mapM shuffleM xs | ||
135 | |||
136 | mapWithURI :: (URI -> a -> b) -> TrackerList a -> TrackerList b | ||
137 | mapWithURI f (Announce (uri, a)) = Announce (uri, f uri a) | ||
138 | mapWithURI f (TierList xs ) = TierList (L.map (L.map mapEntry) xs) | ||
139 | where | ||
140 | mapEntry (uri, a) = (uri, f uri a) | ||
141 | |||
142 | toList :: TrackerList a -> [[TierEntry a]] | ||
143 | toList (Announce e) = [[e]] | ||
144 | toList (TierList xxs) = xxs | ||
145 | |||
146 | {----------------------------------------------------------------------- | ||
147 | -- Special traversals (suppressed RPC exceptions) | ||
148 | -----------------------------------------------------------------------} | ||
149 | |||
150 | catchRPC :: IO a -> IO a -> IO a | ||
151 | catchRPC a b = catch a (f b) | ||
152 | where | ||
153 | f :: a -> RpcException -> a | ||
154 | f = const | ||
155 | |||
156 | throwRPC :: String -> IO a | ||
157 | throwRPC = throwIO . GenericException | ||
158 | |||
159 | -- | Like 'traverse' but ignores 'RpcExceptions'. | ||
160 | traverseAll :: (TierEntry a -> IO a) -> TrackerList a -> IO (TrackerList a) | ||
161 | traverseAll action = traverseWithURI (action $?) | ||
162 | where | ||
163 | f $? x = catchRPC (f x) (return (snd x)) | ||
164 | |||
165 | -- | Like 'traverse' but put working trackers to the head of tiers. | ||
166 | -- This can help to avoid exceessive requests to not available | ||
167 | -- trackers at each reannounce. If no one action succeed then original | ||
168 | -- list is returned. | ||
169 | traverseTiers :: (TierEntry a -> IO a) -> TrackerList a -> IO (TrackerList a) | ||
170 | traverseTiers action ts = catchRPC (goList ts) (return ts) | ||
171 | where | ||
172 | goList tl @ (Announce _ ) = traverseWithURI action tl | ||
173 | goList (TierList tiers) = TierList <$> goTiers (goTier []) tiers | ||
174 | |||
175 | goTiers _ [] = throwRPC "traverseTiers: no tiers" | ||
176 | goTiers f (x : xs) = catchRPC shortcut failback | ||
177 | where | ||
178 | shortcut = do | ||
179 | x' <- f x | ||
180 | return (x' : xs) | ||
181 | |||
182 | failback = do | ||
183 | xs' <- goTiers f xs | ||
184 | return (x : xs') | ||
185 | |||
186 | goTier _ [] = throwRPC "traverseTiers: no trackers in tier" | ||
187 | goTier failed ((uri, a) : as) = catchRPC shortcut failback | ||
188 | where | ||
189 | shortcut = do | ||
190 | a' <- action (uri, a) | ||
191 | return ((uri, a') : as ++ failed) -- failed trackers at the end | ||
192 | |||
193 | failback = goTier ((uri, a) : failed) as | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/Message.hs b/bittorrent/src/Network/BitTorrent/Tracker/Message.hs new file mode 100644 index 00000000..b9b6a9d3 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/Message.hs | |||
@@ -0,0 +1,920 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- (c) Daniel Gröber 2013 | ||
4 | -- License : BSD3 | ||
5 | -- Maintainer : pxqr.sta@gmail.com | ||
6 | -- Stability : experimental | ||
7 | -- Portability : portable | ||
8 | -- | ||
9 | -- Every tracker should support announce query. This query is used | ||
10 | -- to discover peers within a swarm and have two-fold effect: | ||
11 | -- | ||
12 | -- * peer doing announce discover other peers using peer list from | ||
13 | -- the response to the announce query. | ||
14 | -- | ||
15 | -- * tracker store peer information and use it in the succeeding | ||
16 | -- requests made by other peers, until the peer info expires. | ||
17 | -- | ||
18 | -- By convention most trackers support another form of request — | ||
19 | -- scrape query — which queries the state of a given torrent (or | ||
20 | -- a list of torrents) that the tracker is managing. | ||
21 | -- | ||
22 | {-# LANGUAGE FlexibleContexts #-} | ||
23 | {-# LANGUAGE FlexibleInstances #-} | ||
24 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
25 | {-# LANGUAGE TemplateHaskell #-} | ||
26 | {-# LANGUAGE DeriveDataTypeable #-} | ||
27 | {-# LANGUAGE DeriveFunctor #-} | ||
28 | {-# LANGUAGE ScopedTypeVariables #-} | ||
29 | {-# LANGUAGE TypeFamilies #-} | ||
30 | {-# OPTIONS -fno-warn-orphans #-} | ||
31 | module Network.BitTorrent.Tracker.Message | ||
32 | ( -- * Announce | ||
33 | -- ** Query | ||
34 | AnnounceEvent (..) | ||
35 | , AnnounceQuery (..) | ||
36 | , renderAnnounceQuery | ||
37 | , ParamParseFailure | ||
38 | , parseAnnounceQuery | ||
39 | |||
40 | -- ** Info | ||
41 | , PeerList (..) | ||
42 | , getPeerList | ||
43 | , AnnounceInfo(..) | ||
44 | , defaultNumWant | ||
45 | , defaultMaxNumWant | ||
46 | , defaultReannounceInterval | ||
47 | |||
48 | -- * Scrape | ||
49 | -- ** Query | ||
50 | , ScrapeQuery | ||
51 | , renderScrapeQuery | ||
52 | , parseScrapeQuery | ||
53 | |||
54 | -- ** Info | ||
55 | , ScrapeEntry (..) | ||
56 | , ScrapeInfo | ||
57 | |||
58 | -- * HTTP specific | ||
59 | -- ** Routes | ||
60 | , PathPiece | ||
61 | , defaultAnnouncePath | ||
62 | , defaultScrapePath | ||
63 | |||
64 | -- ** Preferences | ||
65 | , AnnouncePrefs (..) | ||
66 | , renderAnnouncePrefs | ||
67 | , parseAnnouncePrefs | ||
68 | |||
69 | -- ** Request | ||
70 | , AnnounceRequest (..) | ||
71 | , parseAnnounceRequest | ||
72 | , renderAnnounceRequest | ||
73 | |||
74 | -- ** Response | ||
75 | , announceType | ||
76 | , scrapeType | ||
77 | , parseFailureStatus | ||
78 | |||
79 | -- ** Extra | ||
80 | , queryToSimpleQuery | ||
81 | |||
82 | -- * UDP specific | ||
83 | -- ** Connection | ||
84 | , ConnectionId | ||
85 | , initialConnectionId | ||
86 | |||
87 | -- ** Messages | ||
88 | , Request (..) | ||
89 | , Response (..) | ||
90 | , responseName | ||
91 | |||
92 | -- ** Transaction | ||
93 | , genTransactionId | ||
94 | , TransactionId | ||
95 | , Transaction (..) | ||
96 | ) | ||
97 | where | ||
98 | |||
99 | import Control.Applicative | ||
100 | import Control.Monad | ||
101 | import Data.BEncode as BE hiding (Result) | ||
102 | import Data.BEncode.BDict as BE | ||
103 | import Data.ByteString as BS | ||
104 | import Data.ByteString.Char8 as BC | ||
105 | import Data.Char as Char | ||
106 | import Data.Convertible | ||
107 | import Data.Default | ||
108 | import Data.Either | ||
109 | import Data.List as L | ||
110 | import Data.Maybe | ||
111 | import Data.Monoid | ||
112 | import Data.Serialize as S hiding (Result) | ||
113 | import Data.String | ||
114 | import Data.Text (Text) | ||
115 | import Data.Text.Encoding | ||
116 | import Data.Typeable | ||
117 | import Data.Word | ||
118 | import Data.IP | ||
119 | import Network | ||
120 | import Network.HTTP.Types.QueryLike | ||
121 | import Network.HTTP.Types.URI hiding (urlEncode) | ||
122 | import Network.HTTP.Types.Status | ||
123 | import Network.Socket hiding (Connected) | ||
124 | import Numeric | ||
125 | import System.Entropy | ||
126 | import Text.Read (readMaybe) | ||
127 | |||
128 | import Data.Torrent | ||
129 | import Network.Address | ||
130 | import Network.BitTorrent.Internal.Progress | ||
131 | |||
132 | {----------------------------------------------------------------------- | ||
133 | -- Events | ||
134 | -----------------------------------------------------------------------} | ||
135 | |||
136 | -- | Events are used to specify which kind of announce query is performed. | ||
137 | data AnnounceEvent | ||
138 | -- | For the first request: when download first begins. | ||
139 | = Started | ||
140 | |||
141 | -- | This peer stopped downloading /and/ uploading the torrent or | ||
142 | -- just shutting down. | ||
143 | | Stopped | ||
144 | |||
145 | -- | This peer completed downloading the torrent. This only happen | ||
146 | -- right after last piece have been verified. No 'Completed' is | ||
147 | -- sent if the file was completed when 'Started'. | ||
148 | | Completed | ||
149 | deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable) | ||
150 | |||
151 | -- | HTTP tracker protocol compatible encoding. | ||
152 | instance QueryValueLike AnnounceEvent where | ||
153 | toQueryValue e = toQueryValue (Char.toLower x : xs) | ||
154 | where | ||
155 | (x : xs) = show e -- INVARIANT: this is always nonempty list | ||
156 | |||
157 | type EventId = Word32 | ||
158 | |||
159 | -- | UDP tracker encoding event codes. | ||
160 | eventId :: AnnounceEvent -> EventId | ||
161 | eventId Completed = 1 | ||
162 | eventId Started = 2 | ||
163 | eventId Stopped = 3 | ||
164 | |||
165 | -- TODO add Regular event | ||
166 | putEvent :: Putter (Maybe AnnounceEvent) | ||
167 | putEvent Nothing = putWord32be 0 | ||
168 | putEvent (Just e) = putWord32be (eventId e) | ||
169 | |||
170 | getEvent :: S.Get (Maybe AnnounceEvent) | ||
171 | getEvent = do | ||
172 | eid <- getWord32be | ||
173 | case eid of | ||
174 | 0 -> return Nothing | ||
175 | 1 -> return $ Just Completed | ||
176 | 2 -> return $ Just Started | ||
177 | 3 -> return $ Just Stopped | ||
178 | _ -> fail "unknown event id" | ||
179 | |||
180 | {----------------------------------------------------------------------- | ||
181 | Announce query | ||
182 | -----------------------------------------------------------------------} | ||
183 | -- TODO add &ipv6= and &ipv4= params to AnnounceQuery | ||
184 | -- http://www.bittorrent.org/beps/bep_0007.html#announce-parameter | ||
185 | |||
186 | -- | A tracker request is HTTP GET request; used to include metrics | ||
187 | -- from clients that help the tracker keep overall statistics about | ||
188 | -- the torrent. The most important, requests are used by the tracker | ||
189 | -- to keep track lists of active peer for a particular torrent. | ||
190 | -- | ||
191 | data AnnounceQuery = AnnounceQuery | ||
192 | { | ||
193 | -- | Hash of info part of the torrent usually obtained from | ||
194 | -- 'Torrent' or 'Magnet'. | ||
195 | reqInfoHash :: !InfoHash | ||
196 | |||
197 | -- | ID of the peer doing request. | ||
198 | , reqPeerId :: !PeerId | ||
199 | |||
200 | -- | Port to listen to for connections from other | ||
201 | -- peers. Tracker should respond with this port when | ||
202 | -- some /other/ peer request the tracker with the same info hash. | ||
203 | -- Normally, this port is choosed from 'defaultPorts'. | ||
204 | , reqPort :: !PortNumber | ||
205 | |||
206 | -- | Current progress of peer doing request. | ||
207 | , reqProgress :: !Progress | ||
208 | |||
209 | -- | The peer IP. Needed only when client communicated with | ||
210 | -- tracker throught a proxy. | ||
211 | , reqIP :: Maybe HostAddress | ||
212 | |||
213 | -- | Number of peers that the peers wants to receive from. It is | ||
214 | -- optional for trackers to honor this limit. See note for | ||
215 | -- 'defaultNumWant'. | ||
216 | , reqNumWant :: Maybe Int | ||
217 | |||
218 | -- | If not specified, the request is regular periodic | ||
219 | -- request. Regular request should be sent | ||
220 | , reqEvent :: Maybe AnnounceEvent | ||
221 | } deriving (Show, Eq, Typeable) | ||
222 | |||
223 | -- | UDP tracker protocol compatible encoding. | ||
224 | instance Serialize AnnounceQuery where | ||
225 | put AnnounceQuery {..} = do | ||
226 | put reqInfoHash | ||
227 | put reqPeerId | ||
228 | put reqProgress | ||
229 | putEvent reqEvent | ||
230 | putWord32host $ fromMaybe 0 reqIP | ||
231 | putWord32be $ 0 -- TODO what the fuck is "key"? | ||
232 | putWord32be $ fromIntegral $ fromMaybe (-1) reqNumWant | ||
233 | |||
234 | put reqPort | ||
235 | |||
236 | get = do | ||
237 | ih <- get | ||
238 | pid <- get | ||
239 | |||
240 | progress <- get | ||
241 | |||
242 | ev <- getEvent | ||
243 | ip <- getWord32be | ||
244 | -- key <- getWord32be -- TODO | ||
245 | want <- getWord32be | ||
246 | |||
247 | port <- get | ||
248 | |||
249 | return $ AnnounceQuery { | ||
250 | reqInfoHash = ih | ||
251 | , reqPeerId = pid | ||
252 | , reqPort = port | ||
253 | , reqProgress = progress | ||
254 | , reqIP = if ip == 0 then Nothing else Just ip | ||
255 | , reqNumWant = if want == -1 then Nothing | ||
256 | else Just (fromIntegral want) | ||
257 | , reqEvent = ev | ||
258 | } | ||
259 | |||
260 | instance QueryValueLike PortNumber where | ||
261 | toQueryValue = toQueryValue . show . fromEnum | ||
262 | |||
263 | instance QueryValueLike Word32 where | ||
264 | toQueryValue = toQueryValue . show | ||
265 | |||
266 | instance QueryValueLike Int where | ||
267 | toQueryValue = toQueryValue . show | ||
268 | |||
269 | -- | HTTP tracker protocol compatible encoding. | ||
270 | instance QueryLike AnnounceQuery where | ||
271 | toQuery AnnounceQuery {..} = | ||
272 | toQuery reqProgress ++ | ||
273 | [ ("info_hash", toQueryValue reqInfoHash) -- TODO use 'paramName' | ||
274 | , ("peer_id" , toQueryValue reqPeerId) | ||
275 | , ("port" , toQueryValue reqPort) | ||
276 | , ("ip" , toQueryValue reqIP) | ||
277 | , ("numwant" , toQueryValue reqNumWant) | ||
278 | , ("event" , toQueryValue reqEvent) | ||
279 | ] | ||
280 | |||
281 | -- | Filter @param=value@ pairs with the unset value. | ||
282 | queryToSimpleQuery :: Query -> SimpleQuery | ||
283 | queryToSimpleQuery = catMaybes . L.map f | ||
284 | where | ||
285 | f (_, Nothing) = Nothing | ||
286 | f (a, Just b ) = Just (a, b) | ||
287 | |||
288 | -- | Encode announce query to query string. | ||
289 | renderAnnounceQuery :: AnnounceQuery -> SimpleQuery | ||
290 | renderAnnounceQuery = queryToSimpleQuery . toQuery | ||
291 | |||
292 | data QueryParam | ||
293 | -- announce query | ||
294 | = ParamInfoHash | ||
295 | | ParamPeerId | ||
296 | | ParamPort | ||
297 | | ParamUploaded | ||
298 | | ParamLeft | ||
299 | | ParamDownloaded | ||
300 | | ParamIP | ||
301 | | ParamNumWant | ||
302 | | ParamEvent | ||
303 | -- announce query ext | ||
304 | | ParamCompact | ||
305 | | ParamNoPeerId | ||
306 | deriving (Show, Eq, Ord, Enum) | ||
307 | |||
308 | paramName :: QueryParam -> BS.ByteString | ||
309 | paramName ParamInfoHash = "info_hash" | ||
310 | paramName ParamPeerId = "peer_id" | ||
311 | paramName ParamPort = "port" | ||
312 | paramName ParamUploaded = "uploaded" | ||
313 | paramName ParamLeft = "left" | ||
314 | paramName ParamDownloaded = "downloaded" | ||
315 | paramName ParamIP = "ip" | ||
316 | paramName ParamNumWant = "numwant" | ||
317 | paramName ParamEvent = "event" | ||
318 | paramName ParamCompact = "compact" | ||
319 | paramName ParamNoPeerId = "no_peer_id" | ||
320 | {-# INLINE paramName #-} | ||
321 | |||
322 | class FromParam a where | ||
323 | fromParam :: BS.ByteString -> Maybe a | ||
324 | |||
325 | instance FromParam Bool where | ||
326 | fromParam "0" = Just False | ||
327 | fromParam "1" = Just True | ||
328 | fromParam _ = Nothing | ||
329 | |||
330 | instance FromParam InfoHash where | ||
331 | fromParam = either (const Nothing) pure . safeConvert | ||
332 | |||
333 | instance FromParam PeerId where | ||
334 | fromParam = either (const Nothing) pure . safeConvert | ||
335 | |||
336 | instance FromParam Word32 where | ||
337 | fromParam = readMaybe . BC.unpack | ||
338 | |||
339 | instance FromParam Word64 where | ||
340 | fromParam = readMaybe . BC.unpack | ||
341 | |||
342 | instance FromParam Int where | ||
343 | fromParam = readMaybe . BC.unpack | ||
344 | |||
345 | instance FromParam PortNumber where | ||
346 | fromParam bs = fromIntegral <$> (fromParam bs :: Maybe Word32) | ||
347 | |||
348 | instance FromParam AnnounceEvent where | ||
349 | fromParam bs = do | ||
350 | (x, xs) <- BC.uncons bs | ||
351 | readMaybe $ BC.unpack $ BC.cons (Char.toUpper x) xs | ||
352 | |||
353 | -- | 'ParamParseFailure' represent errors can occur while parsing HTTP | ||
354 | -- tracker requests. In case of failure, this can be used to provide | ||
355 | -- more informative 'statusCode' and 'statusMessage' in tracker | ||
356 | -- responses. | ||
357 | -- | ||
358 | data ParamParseFailure | ||
359 | = Missing QueryParam -- ^ param not found in query string; | ||
360 | | Invalid QueryParam BS.ByteString -- ^ param present but not valid. | ||
361 | deriving (Show, Eq) | ||
362 | |||
363 | type ParseResult = Either ParamParseFailure | ||
364 | |||
365 | withError :: ParamParseFailure -> Maybe a -> ParseResult a | ||
366 | withError e = maybe (Left e) Right | ||
367 | |||
368 | reqParam :: FromParam a => QueryParam -> SimpleQuery -> ParseResult a | ||
369 | reqParam param xs = do | ||
370 | val <- withError (Missing param) $ L.lookup (paramName param) xs | ||
371 | withError (Invalid param val) (fromParam val) | ||
372 | |||
373 | optParam :: FromParam a => QueryParam -> SimpleQuery -> ParseResult (Maybe a) | ||
374 | optParam param ps | ||
375 | | Just x <- L.lookup (paramName param) ps | ||
376 | = pure <$> withError (Invalid param x) (fromParam x) | ||
377 | | otherwise = pure Nothing | ||
378 | |||
379 | parseProgress :: SimpleQuery -> ParseResult Progress | ||
380 | parseProgress params = Progress | ||
381 | <$> reqParam ParamDownloaded params | ||
382 | <*> reqParam ParamLeft params | ||
383 | <*> reqParam ParamUploaded params | ||
384 | |||
385 | -- | Parse announce request from a query string. | ||
386 | parseAnnounceQuery :: SimpleQuery -> ParseResult AnnounceQuery | ||
387 | parseAnnounceQuery params = AnnounceQuery | ||
388 | <$> reqParam ParamInfoHash params | ||
389 | <*> reqParam ParamPeerId params | ||
390 | <*> reqParam ParamPort params | ||
391 | <*> parseProgress params | ||
392 | <*> optParam ParamIP params | ||
393 | <*> optParam ParamNumWant params | ||
394 | <*> optParam ParamEvent params | ||
395 | |||
396 | {----------------------------------------------------------------------- | ||
397 | -- Announce Info | ||
398 | -----------------------------------------------------------------------} | ||
399 | -- TODO check if announceinterval/complete/incomplete is positive ints | ||
400 | |||
401 | -- | Tracker can return peer list in either compact(BEP23) or not | ||
402 | -- compact form. | ||
403 | -- | ||
404 | -- For more info see: <http://www.bittorrent.org/beps/bep_0023.html> | ||
405 | -- | ||
406 | data PeerList ip | ||
407 | = PeerList [PeerAddr IP] | ||
408 | | CompactPeerList [PeerAddr ip] | ||
409 | deriving (Show, Eq, Typeable, Functor) | ||
410 | |||
411 | -- | The empty non-compact peer list. | ||
412 | instance Default (PeerList IP) where | ||
413 | def = PeerList [] | ||
414 | {-# INLINE def #-} | ||
415 | |||
416 | getPeerList :: PeerList IP -> [PeerAddr IP] | ||
417 | getPeerList (PeerList xs) = xs | ||
418 | getPeerList (CompactPeerList xs) = xs | ||
419 | |||
420 | instance Serialize a => BEncode (PeerList a) where | ||
421 | toBEncode (PeerList xs) = toBEncode xs | ||
422 | toBEncode (CompactPeerList xs) = toBEncode $ runPut (mapM_ put xs) | ||
423 | |||
424 | fromBEncode (BList l ) = PeerList <$> fromBEncode (BList l) | ||
425 | fromBEncode (BString s ) = CompactPeerList <$> runGet (many get) s | ||
426 | fromBEncode _ = decodingError "PeerList: should be a BString or BList" | ||
427 | |||
428 | -- | The tracker response includes a peer list that helps the client | ||
429 | -- participate in the torrent. The most important is 'respPeer' list | ||
430 | -- used to join the swarm. | ||
431 | -- | ||
432 | data AnnounceInfo = | ||
433 | Failure !Text -- ^ Failure reason in human readable form. | ||
434 | | AnnounceInfo { | ||
435 | -- | Number of peers completed the torrent. (seeders) | ||
436 | respComplete :: !(Maybe Int) | ||
437 | |||
438 | -- | Number of peers downloading the torrent. (leechers) | ||
439 | , respIncomplete :: !(Maybe Int) | ||
440 | |||
441 | -- | Recommended interval to wait between requests, in seconds. | ||
442 | , respInterval :: !Int | ||
443 | |||
444 | -- | Minimal amount of time between requests, in seconds. A | ||
445 | -- peer /should/ make timeout with at least 'respMinInterval' | ||
446 | -- value, otherwise tracker might not respond. If not specified | ||
447 | -- the same applies to 'respInterval'. | ||
448 | , respMinInterval :: !(Maybe Int) | ||
449 | |||
450 | -- | Peers that must be contacted. | ||
451 | , respPeers :: !(PeerList IP) | ||
452 | |||
453 | -- | Human readable warning. | ||
454 | , respWarning :: !(Maybe Text) | ||
455 | } deriving (Show, Eq, Typeable) | ||
456 | |||
457 | -- | Empty peer list with default reannounce interval. | ||
458 | instance Default AnnounceInfo where | ||
459 | def = AnnounceInfo | ||
460 | { respComplete = Nothing | ||
461 | , respIncomplete = Nothing | ||
462 | , respInterval = defaultReannounceInterval | ||
463 | , respMinInterval = Nothing | ||
464 | , respPeers = def | ||
465 | , respWarning = Nothing | ||
466 | } | ||
467 | |||
468 | -- | HTTP tracker protocol compatible encoding. | ||
469 | instance BEncode AnnounceInfo where | ||
470 | toBEncode (Failure t) = toDict $ | ||
471 | "failure reason" .=! t | ||
472 | .: endDict | ||
473 | |||
474 | toBEncode AnnounceInfo {..} = toDict $ | ||
475 | "complete" .=? respComplete | ||
476 | .: "incomplete" .=? respIncomplete | ||
477 | .: "interval" .=! respInterval | ||
478 | .: "min interval" .=? respMinInterval | ||
479 | .: "peers" .=! peers | ||
480 | .: "peers6" .=? peers6 | ||
481 | .: "warning message" .=? respWarning | ||
482 | .: endDict | ||
483 | where | ||
484 | (peers, peers6) = prttn respPeers | ||
485 | |||
486 | prttn :: PeerList IP -> (PeerList IPv4, Maybe (PeerList IPv6)) | ||
487 | prttn (PeerList xs) = (PeerList xs, Nothing) | ||
488 | prttn (CompactPeerList xs) = mk $ partitionEithers $ toEither <$> xs | ||
489 | where | ||
490 | mk (v4s, v6s) | ||
491 | | L.null v6s = (CompactPeerList v4s, Nothing) | ||
492 | | otherwise = (CompactPeerList v4s, Just (CompactPeerList v6s)) | ||
493 | |||
494 | toEither :: PeerAddr IP -> Either (PeerAddr IPv4) (PeerAddr IPv6) | ||
495 | toEither PeerAddr {..} = case peerHost of | ||
496 | IPv4 ipv4 -> Left $ PeerAddr peerId ipv4 peerPort | ||
497 | IPv6 ipv6 -> Right $ PeerAddr peerId ipv6 peerPort | ||
498 | |||
499 | fromBEncode (BDict d) | ||
500 | | Just t <- BE.lookup "failure reason" d = Failure <$> fromBEncode t | ||
501 | | otherwise = (`fromDict` (BDict d)) $ | ||
502 | AnnounceInfo | ||
503 | <$>? "complete" | ||
504 | <*>? "incomplete" | ||
505 | <*>! "interval" | ||
506 | <*>? "min interval" | ||
507 | <*> (uncurry merge =<< (,) <$>! "peers" <*>? "peers6") | ||
508 | <*>? "warning message" | ||
509 | where | ||
510 | merge :: PeerList IPv4 -> Maybe (PeerList IPv6) -> BE.Get (PeerList IP) | ||
511 | merge (PeerList ips) Nothing = pure (PeerList ips) | ||
512 | merge (PeerList _ ) (Just _) | ||
513 | = fail "PeerList: non-compact peer list provided, \ | ||
514 | \but the `peers6' field present" | ||
515 | |||
516 | merge (CompactPeerList ipv4s) Nothing | ||
517 | = pure $ CompactPeerList (fmap IPv4 <$> ipv4s) | ||
518 | |||
519 | merge (CompactPeerList _ ) (Just (PeerList _)) | ||
520 | = fail "PeerList: the `peers6' field value \ | ||
521 | \should contain *compact* peer list" | ||
522 | |||
523 | merge (CompactPeerList ipv4s) (Just (CompactPeerList ipv6s)) | ||
524 | = pure $ CompactPeerList $ | ||
525 | (fmap IPv4 <$> ipv4s) <> (fmap IPv6 <$> ipv6s) | ||
526 | |||
527 | fromBEncode _ = decodingError "Announce info" | ||
528 | |||
529 | -- | UDP tracker protocol compatible encoding. | ||
530 | instance Serialize AnnounceInfo where | ||
531 | put (Failure msg) = put $ encodeUtf8 msg | ||
532 | put AnnounceInfo {..} = do | ||
533 | putWord32be $ fromIntegral respInterval | ||
534 | putWord32be $ fromIntegral $ fromMaybe 0 respIncomplete | ||
535 | putWord32be $ fromIntegral $ fromMaybe 0 respComplete | ||
536 | forM_ (fmap ipv4 <$> getPeerList respPeers) put | ||
537 | |||
538 | get = do | ||
539 | interval <- getWord32be | ||
540 | leechers <- getWord32be | ||
541 | seeders <- getWord32be | ||
542 | peers <- many $ fmap IPv4 <$> get | ||
543 | |||
544 | return $ AnnounceInfo { | ||
545 | respWarning = Nothing | ||
546 | , respInterval = fromIntegral interval | ||
547 | , respMinInterval = Nothing | ||
548 | , respIncomplete = Just $ fromIntegral leechers | ||
549 | , respComplete = Just $ fromIntegral seeders | ||
550 | , respPeers = PeerList peers | ||
551 | } | ||
552 | |||
553 | -- | Decodes announce response from bencoded string, for debugging only. | ||
554 | instance IsString AnnounceInfo where | ||
555 | fromString str = either (error . format) id $ BE.decode (fromString str) | ||
556 | where | ||
557 | format msg = "fromString: unable to decode AnnounceInfo: " ++ msg | ||
558 | |||
559 | -- | Above 25, new peers are highly unlikely to increase download | ||
560 | -- speed. Even 30 peers is /plenty/, the official client version 3 | ||
561 | -- in fact only actively forms new connections if it has less than | ||
562 | -- 30 peers and will refuse connections if it has 55. | ||
563 | -- | ||
564 | -- <https://wiki.theory.org/BitTorrent_Tracker_Protocol#Basic_Tracker_Announce_Request> | ||
565 | -- | ||
566 | defaultNumWant :: Int | ||
567 | defaultNumWant = 50 | ||
568 | |||
569 | -- | Reasonable upper bound of numwant parameter. | ||
570 | defaultMaxNumWant :: Int | ||
571 | defaultMaxNumWant = 200 | ||
572 | |||
573 | -- | Widely used reannounce interval. Note: tracker clients should not | ||
574 | -- use this value! | ||
575 | defaultReannounceInterval :: Int | ||
576 | defaultReannounceInterval = 30 * 60 | ||
577 | |||
578 | {----------------------------------------------------------------------- | ||
579 | Scrape message | ||
580 | -----------------------------------------------------------------------} | ||
581 | |||
582 | -- | Scrape query used to specify a set of torrent to scrape. | ||
583 | -- If list is empty then tracker should return scrape info about each | ||
584 | -- torrent. | ||
585 | type ScrapeQuery = [InfoHash] | ||
586 | |||
587 | -- TODO | ||
588 | -- data ScrapeQuery | ||
589 | -- = ScrapeAll | ||
590 | -- | ScrapeSingle InfoHash | ||
591 | -- | ScrapeMulti (HashSet InfoHash) | ||
592 | -- deriving (Show) | ||
593 | -- | ||
594 | -- data ScrapeInfo | ||
595 | -- = ScrapeAll (HashMap InfoHash ScrapeEntry) | ||
596 | -- | ScrapeSingle InfoHash ScrapeEntry | ||
597 | -- | ScrapeMulti (HashMap InfoHash ScrapeEntry) | ||
598 | -- | ||
599 | |||
600 | scrapeParam :: BS.ByteString | ||
601 | scrapeParam = "info_hash" | ||
602 | |||
603 | isScrapeParam :: BS.ByteString -> Bool | ||
604 | isScrapeParam = (==) scrapeParam | ||
605 | |||
606 | -- | Parse scrape query to query string. | ||
607 | parseScrapeQuery :: SimpleQuery -> ScrapeQuery | ||
608 | parseScrapeQuery | ||
609 | = catMaybes . L.map (fromParam . snd) . L.filter (isScrapeParam . fst) | ||
610 | |||
611 | -- | Render scrape query to query string. | ||
612 | renderScrapeQuery :: ScrapeQuery -> SimpleQuery | ||
613 | renderScrapeQuery = queryToSimpleQuery . L.map mkPair | ||
614 | where | ||
615 | mkPair ih = (scrapeParam, toQueryValue ih) | ||
616 | |||
617 | -- | Overall information about particular torrent. | ||
618 | data ScrapeEntry = ScrapeEntry { | ||
619 | -- | Number of seeders - peers with the entire file. | ||
620 | siComplete :: {-# UNPACK #-} !Int | ||
621 | |||
622 | -- | Total number of times the tracker has registered a completion. | ||
623 | , siDownloaded :: {-# UNPACK #-} !Int | ||
624 | |||
625 | -- | Number of leechers. | ||
626 | , siIncomplete :: {-# UNPACK #-} !Int | ||
627 | |||
628 | -- | Name of the torrent file, as specified by the "name" | ||
629 | -- file in the info section of the .torrent file. | ||
630 | , siName :: !(Maybe Text) | ||
631 | } deriving (Show, Eq, Typeable) | ||
632 | |||
633 | -- | HTTP tracker protocol compatible encoding. | ||
634 | instance BEncode ScrapeEntry where | ||
635 | toBEncode ScrapeEntry {..} = toDict $ | ||
636 | "complete" .=! siComplete | ||
637 | .: "downloaded" .=! siDownloaded | ||
638 | .: "incomplete" .=! siIncomplete | ||
639 | .: "name" .=? siName | ||
640 | .: endDict | ||
641 | |||
642 | fromBEncode = fromDict $ ScrapeEntry | ||
643 | <$>! "complete" | ||
644 | <*>! "downloaded" | ||
645 | <*>! "incomplete" | ||
646 | <*>? "name" | ||
647 | |||
648 | -- | UDP tracker protocol compatible encoding. | ||
649 | instance Serialize ScrapeEntry where | ||
650 | put ScrapeEntry {..} = do | ||
651 | putWord32be $ fromIntegral siComplete | ||
652 | putWord32be $ fromIntegral siDownloaded | ||
653 | putWord32be $ fromIntegral siIncomplete | ||
654 | |||
655 | get = ScrapeEntry | ||
656 | <$> (fromIntegral <$> getWord32be) | ||
657 | <*> (fromIntegral <$> getWord32be) | ||
658 | <*> (fromIntegral <$> getWord32be) | ||
659 | <*> pure Nothing | ||
660 | |||
661 | -- | Scrape info about a set of torrents. | ||
662 | type ScrapeInfo = [(InfoHash, ScrapeEntry)] | ||
663 | |||
664 | {----------------------------------------------------------------------- | ||
665 | -- HTTP specific | ||
666 | -----------------------------------------------------------------------} | ||
667 | |||
668 | -- | Some HTTP trackers allow to choose prefered representation of the | ||
669 | -- 'AnnounceInfo'. It's optional for trackers to honor any of this | ||
670 | -- options. | ||
671 | data AnnouncePrefs = AnnouncePrefs | ||
672 | { -- | If specified, "compact" parameter is used to advise the | ||
673 | -- tracker to send peer id list as: | ||
674 | -- | ||
675 | -- * bencoded list (extCompact = Just False); | ||
676 | -- * or more compact binary string (extCompact = Just True). | ||
677 | -- | ||
678 | -- The later is prefered since compact peer list will reduce the | ||
679 | -- size of tracker responses. Hovewer, if tracker do not support | ||
680 | -- this extension then it can return peer list in either form. | ||
681 | -- | ||
682 | -- For more info see: <http://www.bittorrent.org/beps/bep_0023.html> | ||
683 | -- | ||
684 | extCompact :: !(Maybe Bool) | ||
685 | |||
686 | -- | If specified, "no_peer_id" parameter is used advise tracker | ||
687 | -- to either send or not to send peer id in tracker response. | ||
688 | -- Tracker may not support this extension as well. | ||
689 | -- | ||
690 | -- For more info see: | ||
691 | -- <http://permalink.gmane.org/gmane.network.bit-torrent.general/4030> | ||
692 | -- | ||
693 | , extNoPeerId :: !(Maybe Bool) | ||
694 | } deriving (Show, Eq, Typeable) | ||
695 | |||
696 | instance Default AnnouncePrefs where | ||
697 | def = AnnouncePrefs Nothing Nothing | ||
698 | |||
699 | instance QueryLike AnnouncePrefs where | ||
700 | toQuery AnnouncePrefs {..} = | ||
701 | [ ("compact", toQueryFlag <$> extCompact) -- TODO use 'paramName' | ||
702 | , ("no_peer_id", toQueryFlag <$> extNoPeerId) | ||
703 | ] | ||
704 | where | ||
705 | toQueryFlag False = "0" | ||
706 | toQueryFlag True = "1" | ||
707 | |||
708 | -- | Parse announce query extended part from query string. | ||
709 | parseAnnouncePrefs :: SimpleQuery -> AnnouncePrefs | ||
710 | parseAnnouncePrefs params = either (const def) id $ | ||
711 | AnnouncePrefs | ||
712 | <$> optParam ParamCompact params | ||
713 | <*> optParam ParamNoPeerId params | ||
714 | |||
715 | -- | Render announce preferences to query string. | ||
716 | renderAnnouncePrefs :: AnnouncePrefs -> SimpleQuery | ||
717 | renderAnnouncePrefs = queryToSimpleQuery . toQuery | ||
718 | |||
719 | -- | HTTP tracker request with preferences. | ||
720 | data AnnounceRequest = AnnounceRequest | ||
721 | { announceQuery :: AnnounceQuery -- ^ Request query params. | ||
722 | , announcePrefs :: AnnouncePrefs -- ^ Optional advises to the tracker. | ||
723 | } deriving (Show, Eq, Typeable) | ||
724 | |||
725 | instance QueryLike AnnounceRequest where | ||
726 | toQuery AnnounceRequest{..} = | ||
727 | toQuery announcePrefs <> | ||
728 | toQuery announceQuery | ||
729 | |||
730 | -- | Parse announce request from query string. | ||
731 | parseAnnounceRequest :: SimpleQuery -> ParseResult AnnounceRequest | ||
732 | parseAnnounceRequest params = AnnounceRequest | ||
733 | <$> parseAnnounceQuery params | ||
734 | <*> pure (parseAnnouncePrefs params) | ||
735 | |||
736 | -- | Render announce request to query string. | ||
737 | renderAnnounceRequest :: AnnounceRequest -> SimpleQuery | ||
738 | renderAnnounceRequest = queryToSimpleQuery . toQuery | ||
739 | |||
740 | type PathPiece = BS.ByteString | ||
741 | |||
742 | defaultAnnouncePath :: PathPiece | ||
743 | defaultAnnouncePath = "announce" | ||
744 | |||
745 | defaultScrapePath :: PathPiece | ||
746 | defaultScrapePath = "scrape" | ||
747 | |||
748 | missingOffset :: Int | ||
749 | missingOffset = 101 | ||
750 | |||
751 | invalidOffset :: Int | ||
752 | invalidOffset = 150 | ||
753 | |||
754 | parseFailureCode :: ParamParseFailure -> Int | ||
755 | parseFailureCode (Missing param ) = missingOffset + fromEnum param | ||
756 | parseFailureCode (Invalid param _) = invalidOffset + fromEnum param | ||
757 | |||
758 | parseFailureMessage :: ParamParseFailure -> BS.ByteString | ||
759 | parseFailureMessage e = BS.concat $ case e of | ||
760 | Missing p -> ["Missing parameter: ", paramName p] | ||
761 | Invalid p v -> ["Invalid parameter: ", paramName p, " = ", v] | ||
762 | |||
763 | -- | HTTP response /content type/ for announce info. | ||
764 | announceType :: ByteString | ||
765 | announceType = "text/plain" | ||
766 | |||
767 | -- | HTTP response /content type/ for scrape info. | ||
768 | scrapeType :: ByteString | ||
769 | scrapeType = "text/plain" | ||
770 | |||
771 | -- | Get HTTP response status from a announce params parse failure. | ||
772 | -- | ||
773 | -- For more info see: | ||
774 | -- <https://wiki.theory.org/BitTorrent_Tracker_Protocol#Response_Codes> | ||
775 | -- | ||
776 | parseFailureStatus :: ParamParseFailure -> Status | ||
777 | parseFailureStatus = mkStatus <$> parseFailureCode <*> parseFailureMessage | ||
778 | |||
779 | {----------------------------------------------------------------------- | ||
780 | -- UDP specific message types | ||
781 | -----------------------------------------------------------------------} | ||
782 | |||
783 | genToken :: IO Word64 | ||
784 | genToken = do | ||
785 | bs <- getEntropy 8 | ||
786 | either err return $ runGet getWord64be bs | ||
787 | where | ||
788 | err = error "genToken: impossible happen" | ||
789 | |||
790 | -- | Connection Id is used for entire tracker session. | ||
791 | newtype ConnectionId = ConnectionId Word64 | ||
792 | deriving (Eq, Serialize) | ||
793 | |||
794 | instance Show ConnectionId where | ||
795 | showsPrec _ (ConnectionId cid) = showString "0x" <> showHex cid | ||
796 | |||
797 | initialConnectionId :: ConnectionId | ||
798 | initialConnectionId = ConnectionId 0x41727101980 | ||
799 | |||
800 | -- | Transaction Id is used within a UDP RPC. | ||
801 | newtype TransactionId = TransactionId Word32 | ||
802 | deriving (Eq, Ord, Enum, Bounded, Serialize) | ||
803 | |||
804 | instance Show TransactionId where | ||
805 | showsPrec _ (TransactionId tid) = showString "0x" <> showHex tid | ||
806 | |||
807 | genTransactionId :: IO TransactionId | ||
808 | genTransactionId = (TransactionId . fromIntegral) <$> genToken | ||
809 | |||
810 | data Request | ||
811 | = Connect | ||
812 | | Announce AnnounceQuery | ||
813 | | Scrape ScrapeQuery | ||
814 | deriving Show | ||
815 | |||
816 | data Response | ||
817 | = Connected ConnectionId | ||
818 | | Announced AnnounceInfo | ||
819 | | Scraped [ScrapeEntry] | ||
820 | | Failed Text | ||
821 | deriving Show | ||
822 | |||
823 | responseName :: Response -> String | ||
824 | responseName (Connected _) = "connected" | ||
825 | responseName (Announced _) = "announced" | ||
826 | responseName (Scraped _) = "scraped" | ||
827 | responseName (Failed _) = "failed" | ||
828 | |||
829 | data family Transaction a | ||
830 | data instance Transaction Request = TransactionQ | ||
831 | { connIdQ :: {-# UNPACK #-} !ConnectionId | ||
832 | , transIdQ :: {-# UNPACK #-} !TransactionId | ||
833 | , request :: !Request | ||
834 | } deriving Show | ||
835 | data instance Transaction Response = TransactionR | ||
836 | { transIdR :: {-# UNPACK #-} !TransactionId | ||
837 | , response :: !Response | ||
838 | } deriving Show | ||
839 | |||
840 | -- TODO newtype | ||
841 | newtype MessageId = MessageId Word32 | ||
842 | deriving (Show, Eq, Num, Serialize) | ||
843 | |||
844 | connectId, announceId, scrapeId, errorId :: MessageId | ||
845 | connectId = 0 | ||
846 | announceId = 1 | ||
847 | scrapeId = 2 | ||
848 | errorId = 3 | ||
849 | |||
850 | instance Serialize (Transaction Request) where | ||
851 | put TransactionQ {..} = do | ||
852 | case request of | ||
853 | Connect -> do | ||
854 | put initialConnectionId | ||
855 | put connectId | ||
856 | put transIdQ | ||
857 | |||
858 | Announce ann -> do | ||
859 | put connIdQ | ||
860 | put announceId | ||
861 | put transIdQ | ||
862 | put ann | ||
863 | |||
864 | Scrape hashes -> do | ||
865 | put connIdQ | ||
866 | put scrapeId | ||
867 | put transIdQ | ||
868 | forM_ hashes put | ||
869 | |||
870 | get = do | ||
871 | cid <- get | ||
872 | mid <- get | ||
873 | TransactionQ cid <$> S.get <*> getBody mid | ||
874 | where | ||
875 | getBody :: MessageId -> S.Get Request | ||
876 | getBody msgId | ||
877 | | msgId == connectId = pure Connect | ||
878 | | msgId == announceId = Announce <$> get | ||
879 | | msgId == scrapeId = Scrape <$> many get | ||
880 | | otherwise = fail errMsg | ||
881 | where | ||
882 | errMsg = "unknown request: " ++ show msgId | ||
883 | |||
884 | instance Serialize (Transaction Response) where | ||
885 | put TransactionR {..} = do | ||
886 | case response of | ||
887 | Connected conn -> do | ||
888 | put connectId | ||
889 | put transIdR | ||
890 | put conn | ||
891 | |||
892 | Announced info -> do | ||
893 | put announceId | ||
894 | put transIdR | ||
895 | put info | ||
896 | |||
897 | Scraped infos -> do | ||
898 | put scrapeId | ||
899 | put transIdR | ||
900 | forM_ infos put | ||
901 | |||
902 | Failed info -> do | ||
903 | put errorId | ||
904 | put transIdR | ||
905 | put (encodeUtf8 info) | ||
906 | |||
907 | |||
908 | get = do | ||
909 | mid <- get | ||
910 | TransactionR <$> get <*> getBody mid | ||
911 | where | ||
912 | getBody :: MessageId -> S.Get Response | ||
913 | getBody msgId | ||
914 | | msgId == connectId = Connected <$> get | ||
915 | | msgId == announceId = Announced <$> get | ||
916 | | msgId == scrapeId = Scraped <$> many get | ||
917 | | msgId == errorId = (Failed . decodeUtf8) <$> get | ||
918 | | otherwise = fail msg | ||
919 | where | ||
920 | msg = "unknown response: " ++ show msgId | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs b/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs new file mode 100644 index 00000000..45fef05e --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/RPC.hs | |||
@@ -0,0 +1,175 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This module provides unified RPC interface to BitTorrent | ||
9 | -- trackers. The tracker is an UDP/HTTP/HTTPS service used to | ||
10 | -- discovery peers for a particular existing torrent and keep | ||
11 | -- statistics about the swarm. This module also provides a way to | ||
12 | -- request scrape info for a particular torrent list. | ||
13 | -- | ||
14 | {-# LANGUAGE DeriveDataTypeable #-} | ||
15 | module Network.BitTorrent.Tracker.RPC | ||
16 | ( PeerInfo (..) | ||
17 | |||
18 | -- * Manager | ||
19 | , Options (..) | ||
20 | , Manager | ||
21 | , newManager | ||
22 | , closeManager | ||
23 | , withManager | ||
24 | |||
25 | -- * RPC | ||
26 | , SAnnounceQuery (..) | ||
27 | , RpcException (..) | ||
28 | , Network.BitTorrent.Tracker.RPC.announce | ||
29 | , scrape | ||
30 | ) where | ||
31 | |||
32 | import Control.Exception | ||
33 | import Data.Default | ||
34 | import Data.Typeable | ||
35 | import Network | ||
36 | import Network.URI | ||
37 | import Network.Socket (HostAddress) | ||
38 | |||
39 | import Data.Torrent | ||
40 | import Network.Address | ||
41 | import Network.BitTorrent.Internal.Progress | ||
42 | import Network.BitTorrent.Tracker.Message | ||
43 | import qualified Network.BitTorrent.Tracker.RPC.HTTP as HTTP | ||
44 | import qualified Network.BitTorrent.Tracker.RPC.UDP as UDP | ||
45 | |||
46 | |||
47 | {----------------------------------------------------------------------- | ||
48 | -- Simplified announce | ||
49 | -----------------------------------------------------------------------} | ||
50 | |||
51 | -- | Info to advertise to trackers. | ||
52 | data PeerInfo = PeerInfo | ||
53 | { peerId :: !PeerId | ||
54 | , peerIP :: !(Maybe HostAddress) | ||
55 | , peerPort :: !PortNumber | ||
56 | } deriving (Show, Eq) | ||
57 | |||
58 | instance Default PeerInfo where | ||
59 | def = PeerInfo def Nothing 6881 | ||
60 | |||
61 | -- | Simplified announce query. | ||
62 | data SAnnounceQuery = SAnnounceQuery | ||
63 | { sInfoHash :: InfoHash | ||
64 | , sProgress :: Progress | ||
65 | , sNumWant :: Maybe Int | ||
66 | , sEvent :: Maybe AnnounceEvent | ||
67 | } | ||
68 | |||
69 | fillAnnounceQuery :: PeerInfo -> SAnnounceQuery -> AnnounceQuery | ||
70 | fillAnnounceQuery PeerInfo{..} SAnnounceQuery {..} = AnnounceQuery | ||
71 | { reqInfoHash = sInfoHash | ||
72 | , reqPeerId = peerId | ||
73 | , reqPort = peerPort | ||
74 | , reqProgress = sProgress | ||
75 | , reqIP = peerIP | ||
76 | , reqNumWant = sNumWant | ||
77 | , reqEvent = sEvent | ||
78 | } | ||
79 | |||
80 | {----------------------------------------------------------------------- | ||
81 | -- RPC manager | ||
82 | -----------------------------------------------------------------------} | ||
83 | |||
84 | -- | Tracker manager settings. | ||
85 | data Options = Options | ||
86 | { -- | HTTP tracker protocol specific options. | ||
87 | optHttpRPC :: !HTTP.Options | ||
88 | |||
89 | -- | UDP tracker protocol specific options. | ||
90 | , optUdpRPC :: !UDP.Options | ||
91 | |||
92 | -- | Whether to use multitracker extension. | ||
93 | , optMultitracker :: !Bool | ||
94 | } | ||
95 | |||
96 | instance Default Options where | ||
97 | def = Options | ||
98 | { optHttpRPC = def | ||
99 | , optUdpRPC = def | ||
100 | , optMultitracker = True | ||
101 | } | ||
102 | |||
103 | -- | Tracker RPC Manager. | ||
104 | data Manager = Manager | ||
105 | { options :: !Options | ||
106 | , peerInfo :: !PeerInfo | ||
107 | , httpMgr :: !HTTP.Manager | ||
108 | , udpMgr :: !UDP.Manager | ||
109 | } | ||
110 | |||
111 | -- | Create a new 'Manager'. You /must/ manually 'closeManager' | ||
112 | -- otherwise resource leakage is possible. Normally, a bittorrent | ||
113 | -- client need a single RPC manager only. | ||
114 | -- | ||
115 | -- This function can throw 'IOException' on invalid 'Options'. | ||
116 | -- | ||
117 | newManager :: Options -> PeerInfo -> IO Manager | ||
118 | newManager opts info = do | ||
119 | h <- HTTP.newManager (optHttpRPC opts) | ||
120 | u <- UDP.newManager (optUdpRPC opts) `onException` HTTP.closeManager h | ||
121 | return $ Manager opts info h u | ||
122 | |||
123 | -- | Close all pending RPCs. Behaviour of currently in-flight RPCs can | ||
124 | -- differ depending on underlying protocol used. No rpc calls should | ||
125 | -- be performed after manager becomes closed. | ||
126 | closeManager :: Manager -> IO () | ||
127 | closeManager Manager {..} = do | ||
128 | UDP.closeManager udpMgr `finally` HTTP.closeManager httpMgr | ||
129 | |||
130 | -- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'. | ||
131 | withManager :: Options -> PeerInfo -> (Manager -> IO a) -> IO a | ||
132 | withManager opts info = bracket (newManager opts info) closeManager | ||
133 | |||
134 | {----------------------------------------------------------------------- | ||
135 | -- Exceptions | ||
136 | -----------------------------------------------------------------------} | ||
137 | -- TODO Catch IO exceptions on rpc calls (?) | ||
138 | |||
139 | data RpcException | ||
140 | = UdpException UDP.RpcException -- ^ UDP RPC driver failure; | ||
141 | | HttpException HTTP.RpcException -- ^ HTTP RPC driver failure; | ||
142 | | UnrecognizedScheme String -- ^ unsupported scheme in announce URI; | ||
143 | | GenericException String -- ^ for furter extensibility. | ||
144 | deriving (Show, Typeable) | ||
145 | |||
146 | instance Exception RpcException | ||
147 | |||
148 | packException :: Exception e => (e -> RpcException) -> IO a -> IO a | ||
149 | packException f m = try m >>= either (throwIO . f) return | ||
150 | {-# INLINE packException #-} | ||
151 | |||
152 | {----------------------------------------------------------------------- | ||
153 | -- RPC calls | ||
154 | -----------------------------------------------------------------------} | ||
155 | |||
156 | dispatch :: URI -> IO a -> IO a -> IO a | ||
157 | dispatch URI {..} http udp | ||
158 | | uriScheme == "http:" || | ||
159 | uriScheme == "https:" = packException HttpException http | ||
160 | | uriScheme == "udp:" = packException UdpException udp | ||
161 | | otherwise = throwIO $ UnrecognizedScheme uriScheme | ||
162 | |||
163 | announce :: Manager -> URI -> SAnnounceQuery -> IO AnnounceInfo | ||
164 | announce Manager {..} uri simpleQuery | ||
165 | = dispatch uri | ||
166 | (HTTP.announce httpMgr uri annQ) | ||
167 | ( UDP.announce udpMgr uri annQ) | ||
168 | where | ||
169 | annQ = fillAnnounceQuery peerInfo simpleQuery | ||
170 | |||
171 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo | ||
172 | scrape Manager {..} uri q | ||
173 | = dispatch uri | ||
174 | (HTTP.scrape httpMgr uri q) | ||
175 | ( UDP.scrape udpMgr uri q) | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/RPC/HTTP.hs b/bittorrent/src/Network/BitTorrent/Tracker/RPC/HTTP.hs new file mode 100644 index 00000000..9b6e056a --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/RPC/HTTP.hs | |||
@@ -0,0 +1,191 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : provisional | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This module implement HTTP tracker protocol. | ||
9 | -- | ||
10 | -- For more information see: | ||
11 | -- <https://wiki.theory.org/BitTorrentSpecification#Tracker_HTTP.2FHTTPS_Protocol> | ||
12 | -- | ||
13 | {-# LANGUAGE DeriveDataTypeable #-} | ||
14 | module Network.BitTorrent.Tracker.RPC.HTTP | ||
15 | ( -- * Manager | ||
16 | Options (..) | ||
17 | , Manager | ||
18 | , newManager | ||
19 | , closeManager | ||
20 | , withManager | ||
21 | |||
22 | -- * RPC | ||
23 | , RpcException (..) | ||
24 | , announce | ||
25 | , scrape | ||
26 | , scrapeOne | ||
27 | ) where | ||
28 | |||
29 | import Control.Applicative | ||
30 | import Control.Exception | ||
31 | import Control.Monad | ||
32 | import Control.Monad.Trans.Resource | ||
33 | import Data.BEncode as BE | ||
34 | import Data.ByteString as BS | ||
35 | import Data.ByteString.Char8 as BC | ||
36 | import Data.ByteString.Lazy as BL | ||
37 | import Data.Default | ||
38 | import Data.List as L | ||
39 | import Data.Monoid | ||
40 | import Data.Typeable hiding (Proxy) | ||
41 | import Network.URI | ||
42 | import Network.HTTP.Conduit hiding | ||
43 | (Manager, newManager, closeManager, withManager) | ||
44 | import Network.HTTP.Client (defaultManagerSettings) | ||
45 | import Network.HTTP.Client.Internal (setUri) | ||
46 | import qualified Network.HTTP.Conduit as HTTP | ||
47 | import Network.HTTP.Types.Header (hUserAgent) | ||
48 | import Network.HTTP.Types.URI (SimpleQuery, renderSimpleQuery) | ||
49 | |||
50 | import Data.Torrent (InfoHash) | ||
51 | import Network.Address (libUserAgent) | ||
52 | import Network.BitTorrent.Tracker.Message hiding (Request, Response) | ||
53 | |||
54 | {----------------------------------------------------------------------- | ||
55 | -- Exceptions | ||
56 | -----------------------------------------------------------------------} | ||
57 | |||
58 | data RpcException | ||
59 | = RequestFailed HttpException -- ^ failed HTTP request. | ||
60 | | ParserFailure String -- ^ unable to decode tracker response; | ||
61 | | ScrapelessTracker -- ^ tracker do not support scraping; | ||
62 | | BadScrape -- ^ unable to find info hash in response dict; | ||
63 | deriving (Show, Typeable) | ||
64 | |||
65 | instance Exception RpcException | ||
66 | |||
67 | packHttpException :: IO a -> IO a | ||
68 | packHttpException m = try m >>= either (throwIO . RequestFailed) return | ||
69 | |||
70 | {----------------------------------------------------------------------- | ||
71 | -- Manager | ||
72 | -----------------------------------------------------------------------} | ||
73 | |||
74 | -- | HTTP tracker specific RPC options. | ||
75 | data Options = Options | ||
76 | { -- | Global HTTP announce query preferences. | ||
77 | optAnnouncePrefs :: !AnnouncePrefs | ||
78 | |||
79 | -- | Whether to use HTTP proxy for HTTP tracker requests. | ||
80 | , optHttpProxy :: !(Maybe Proxy) | ||
81 | |||
82 | -- | Value to put in HTTP user agent header. | ||
83 | , optUserAgent :: !BS.ByteString | ||
84 | |||
85 | -- | HTTP manager options. | ||
86 | , optHttpOptions :: !ManagerSettings | ||
87 | } | ||
88 | |||
89 | instance Default Options where | ||
90 | def = Options | ||
91 | { optAnnouncePrefs = def | ||
92 | , optHttpProxy = Nothing | ||
93 | , optUserAgent = BC.pack libUserAgent | ||
94 | , optHttpOptions = defaultManagerSettings | ||
95 | } | ||
96 | |||
97 | -- | HTTP tracker manager. | ||
98 | data Manager = Manager | ||
99 | { options :: !Options | ||
100 | , httpMgr :: !HTTP.Manager | ||
101 | } | ||
102 | |||
103 | -- | | ||
104 | newManager :: Options -> IO Manager | ||
105 | newManager opts = Manager opts <$> HTTP.newManager (optHttpOptions opts) | ||
106 | |||
107 | -- | | ||
108 | closeManager :: Manager -> IO () | ||
109 | closeManager Manager {..} = HTTP.closeManager httpMgr | ||
110 | |||
111 | -- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'. | ||
112 | withManager :: Options -> (Manager -> IO a) -> IO a | ||
113 | withManager opts = bracket (newManager opts) closeManager | ||
114 | |||
115 | {----------------------------------------------------------------------- | ||
116 | -- Queries | ||
117 | -----------------------------------------------------------------------} | ||
118 | |||
119 | fillRequest :: Options -> SimpleQuery -> Request -> Request | ||
120 | fillRequest Options {..} q r = r | ||
121 | { queryString = joinQuery (queryString r) (renderSimpleQuery False q) | ||
122 | , requestHeaders = (hUserAgent, optUserAgent) : requestHeaders r | ||
123 | , proxy = optHttpProxy | ||
124 | } | ||
125 | where | ||
126 | joinQuery a b | ||
127 | | BS.null a = b | ||
128 | | otherwise = a <> "&" <> b | ||
129 | |||
130 | httpTracker :: BEncode a => Manager -> URI -> SimpleQuery -> IO a | ||
131 | httpTracker Manager {..} uri q = packHttpException $ do | ||
132 | request <- fillRequest options q <$> setUri def {- http-client instance for Request -} uri | ||
133 | response <- runResourceT $ httpLbs request httpMgr | ||
134 | case BE.decode $ BL.toStrict $ responseBody response of | ||
135 | Left msg -> throwIO (ParserFailure msg) | ||
136 | Right info -> return info | ||
137 | |||
138 | {----------------------------------------------------------------------- | ||
139 | -- RPC | ||
140 | -----------------------------------------------------------------------} | ||
141 | |||
142 | -- | Send request and receive response from the tracker specified in | ||
143 | -- announce list. | ||
144 | -- | ||
145 | -- This function can throw 'RpcException'. | ||
146 | -- | ||
147 | announce :: Manager -> URI -> AnnounceQuery -> IO AnnounceInfo | ||
148 | announce mgr uri q = httpTracker mgr uri (renderAnnounceRequest uriQ) | ||
149 | where | ||
150 | uriQ = AnnounceRequest | ||
151 | { announceQuery = q | ||
152 | , announcePrefs = optAnnouncePrefs (options mgr) | ||
153 | } | ||
154 | |||
155 | -- | Trying to convert /announce/ URL to /scrape/ URL. If 'scrapeURL' | ||
156 | -- gives 'Nothing' then tracker do not support scraping. | ||
157 | -- | ||
158 | scrapeURL :: URI -> Maybe URI | ||
159 | scrapeURL uri = do | ||
160 | newPath <- replace (BC.pack (uriPath uri)) | ||
161 | return uri { uriPath = BC.unpack newPath } | ||
162 | where | ||
163 | replace p = do | ||
164 | let ps = BC.splitWith (== '/') p | ||
165 | guard (not (L.null ps)) | ||
166 | guard ("announce" `BS.isPrefixOf` L.last ps) | ||
167 | let newSuff = "scrape" <> BS.drop (BS.length "announce") (L.last ps) | ||
168 | return (BS.intercalate "/" (L.init ps ++ [newSuff])) | ||
169 | |||
170 | -- | For each 'InfoHash' of torrents request scrape info from the tracker. | ||
171 | -- However if the info hash list is 'null', the tracker should list | ||
172 | -- all available torrents. | ||
173 | -- | ||
174 | -- This function can throw 'RpcException'. | ||
175 | -- | ||
176 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo | ||
177 | scrape m u q = do | ||
178 | case scrapeURL u of | ||
179 | Nothing -> throwIO ScrapelessTracker | ||
180 | Just uri -> httpTracker m uri (renderScrapeQuery q) | ||
181 | |||
182 | -- | More particular version of 'scrape', just for one torrent. | ||
183 | -- | ||
184 | -- This function can throw 'RpcException'. | ||
185 | -- | ||
186 | scrapeOne :: Manager -> URI -> InfoHash -> IO ScrapeEntry | ||
187 | scrapeOne m uri ih = do | ||
188 | xs <- scrape m uri [ih] | ||
189 | case L.lookup ih xs of | ||
190 | Nothing -> throwIO BadScrape | ||
191 | Just a -> return a | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/RPC/UDP.hs b/bittorrent/src/Network/BitTorrent/Tracker/RPC/UDP.hs new file mode 100644 index 00000000..31b6b870 --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/RPC/UDP.hs | |||
@@ -0,0 +1,454 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013-2014 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : provisional | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This module implement UDP tracker protocol. | ||
9 | -- | ||
10 | -- For protocol details and uri scheme see: | ||
11 | -- <http://www.bittorrent.org/beps/bep_0015.html>, | ||
12 | -- <https://www.iana.org/assignments/uri-schemes/prov/udp> | ||
13 | -- | ||
14 | {-# LANGUAGE RecordWildCards #-} | ||
15 | {-# LANGUAGE FlexibleInstances #-} | ||
16 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
17 | {-# LANGUAGE DeriveDataTypeable #-} | ||
18 | module Network.BitTorrent.Tracker.RPC.UDP | ||
19 | ( -- * Manager | ||
20 | Options (..) | ||
21 | , Manager | ||
22 | , newManager | ||
23 | , closeManager | ||
24 | , withManager | ||
25 | |||
26 | -- * RPC | ||
27 | , RpcException (..) | ||
28 | , announce | ||
29 | , scrape | ||
30 | ) where | ||
31 | |||
32 | import Control.Applicative | ||
33 | import Control.Concurrent | ||
34 | import Control.Exception | ||
35 | import Control.Monad | ||
36 | import Data.Default | ||
37 | import Data.IORef | ||
38 | import Data.List as L | ||
39 | import Data.Map as M | ||
40 | import Data.Maybe | ||
41 | import Data.Serialize | ||
42 | import Data.Text as T | ||
43 | import Data.Time | ||
44 | import Data.Time.Clock.POSIX | ||
45 | import Data.Traversable | ||
46 | import Data.Typeable | ||
47 | import Text.Read (readMaybe) | ||
48 | import Network.Socket hiding (Connected, connect, listen) | ||
49 | import Network.Socket.ByteString as BS | ||
50 | import Network.URI | ||
51 | import System.Timeout | ||
52 | |||
53 | import Network.BitTorrent.Tracker.Message | ||
54 | |||
55 | {----------------------------------------------------------------------- | ||
56 | -- Options | ||
57 | -----------------------------------------------------------------------} | ||
58 | |||
59 | -- | 'System.Timeout.timeout' specific. | ||
60 | sec :: Int | ||
61 | sec = 1000000 | ||
62 | |||
63 | -- | See <http://www.bittorrent.org/beps/bep_0015.html#time-outs> | ||
64 | defMinTimeout :: Int | ||
65 | defMinTimeout = 15 | ||
66 | |||
67 | -- | See <http://www.bittorrent.org/beps/bep_0015.html#time-outs> | ||
68 | defMaxTimeout :: Int | ||
69 | defMaxTimeout = 15 * 2 ^ (8 :: Int) | ||
70 | |||
71 | -- | See: <http://www.bittorrent.org/beps/bep_0015.html#time-outs> | ||
72 | defMultiplier :: Int | ||
73 | defMultiplier = 2 | ||
74 | |||
75 | -- TODO why 98? | ||
76 | defMaxPacketSize :: Int | ||
77 | defMaxPacketSize = 98 | ||
78 | |||
79 | -- | Manager configuration. | ||
80 | data Options = Options | ||
81 | { -- | Max size of a /response/ packet. | ||
82 | -- | ||
83 | -- 'optMaxPacketSize' /must/ be a positive value. | ||
84 | -- | ||
85 | optMaxPacketSize :: {-# UNPACK #-} !Int | ||
86 | |||
87 | -- | Starting timeout interval in seconds. If a response is not | ||
88 | -- received after 'optMinTimeout' then 'Manager' repeat RPC with | ||
89 | -- timeout interval multiplied by 'optMultiplier' and so on until | ||
90 | -- timeout interval reach 'optMaxTimeout'. | ||
91 | -- | ||
92 | -- 'optMinTimeout' /must/ be a positive value. | ||
93 | -- | ||
94 | , optMinTimeout :: {-# UNPACK #-} !Int | ||
95 | |||
96 | -- | Final timeout interval in seconds. After 'optMaxTimeout' | ||
97 | -- reached and tracker still not responding both 'announce' and | ||
98 | -- 'scrape' functions will throw 'TimeoutExpired' exception. | ||
99 | -- | ||
100 | -- 'optMaxTimeout' /must/ be greater than 'optMinTimeout'. | ||
101 | -- | ||
102 | , optMaxTimeout :: {-# UNPACK #-} !Int | ||
103 | |||
104 | -- | 'optMultiplier' /must/ be a positive value. | ||
105 | , optMultiplier :: {-# UNPACK #-} !Int | ||
106 | } deriving (Show, Eq) | ||
107 | |||
108 | -- | Options suitable for bittorrent client. | ||
109 | instance Default Options where | ||
110 | def = Options | ||
111 | { optMaxPacketSize = defMaxPacketSize | ||
112 | , optMinTimeout = defMinTimeout | ||
113 | , optMaxTimeout = defMaxTimeout | ||
114 | , optMultiplier = defMultiplier | ||
115 | } | ||
116 | |||
117 | checkOptions :: Options -> IO () | ||
118 | checkOptions Options {..} = do | ||
119 | unless (optMaxPacketSize > 0) $ do | ||
120 | throwIO $ userError "optMaxPacketSize must be positive" | ||
121 | |||
122 | unless (optMinTimeout > 0) $ do | ||
123 | throwIO $ userError "optMinTimeout must be positive" | ||
124 | |||
125 | unless (optMaxTimeout > 0) $ do | ||
126 | throwIO $ userError "optMaxTimeout must be positive" | ||
127 | |||
128 | unless (optMultiplier > 0) $ do | ||
129 | throwIO $ userError "optMultiplier must be positive" | ||
130 | |||
131 | unless (optMaxTimeout > optMinTimeout) $ do | ||
132 | throwIO $ userError "optMaxTimeout must be greater than optMinTimeout" | ||
133 | |||
134 | |||
135 | {----------------------------------------------------------------------- | ||
136 | -- Manager state | ||
137 | -----------------------------------------------------------------------} | ||
138 | |||
139 | type ConnectionCache = Map SockAddr Connection | ||
140 | |||
141 | type PendingResponse = MVar (Either RpcException Response) | ||
142 | type PendingTransactions = Map TransactionId PendingResponse | ||
143 | type PendingQueries = Map SockAddr PendingTransactions | ||
144 | |||
145 | -- | UDP tracker manager. | ||
146 | data Manager = Manager | ||
147 | { options :: !Options | ||
148 | , sock :: !Socket | ||
149 | -- , dnsCache :: !(IORef (Map URI SockAddr)) | ||
150 | , connectionCache :: !(IORef ConnectionCache) | ||
151 | , pendingResps :: !(MVar PendingQueries) | ||
152 | , listenerThread :: !(MVar ThreadId) | ||
153 | } | ||
154 | |||
155 | initManager :: Options -> IO Manager | ||
156 | initManager opts = Manager opts | ||
157 | <$> socket AF_INET Datagram defaultProtocol | ||
158 | <*> newIORef M.empty | ||
159 | <*> newMVar M.empty | ||
160 | <*> newEmptyMVar | ||
161 | |||
162 | unblockAll :: PendingQueries -> IO () | ||
163 | unblockAll m = traverse (traverse unblockCall) m >> return () | ||
164 | where | ||
165 | unblockCall ares = putMVar ares (Left ManagerClosed) | ||
166 | |||
167 | resetState :: Manager -> IO () | ||
168 | resetState Manager {..} = do | ||
169 | writeIORef connectionCache err | ||
170 | m <- swapMVar pendingResps err | ||
171 | unblockAll m | ||
172 | mtid <- tryTakeMVar listenerThread | ||
173 | case mtid of | ||
174 | Nothing -> return () -- thread killed by 'closeManager' | ||
175 | Just _ -> return () -- thread killed by exception from 'listen' | ||
176 | return () | ||
177 | where | ||
178 | err = error "UDP tracker manager closed" | ||
179 | |||
180 | -- | This function will throw 'IOException' on invalid 'Options'. | ||
181 | newManager :: Options -> IO Manager | ||
182 | newManager opts = do | ||
183 | checkOptions opts | ||
184 | mgr <- initManager opts | ||
185 | tid <- forkIO (listen mgr `finally` resetState mgr) | ||
186 | putMVar (listenerThread mgr) tid | ||
187 | return mgr | ||
188 | |||
189 | -- | Unblock all RPCs by throwing 'ManagerClosed' exception. No rpc | ||
190 | -- calls should be performed after manager becomes closed. | ||
191 | closeManager :: Manager -> IO () | ||
192 | closeManager Manager {..} = do | ||
193 | close sock | ||
194 | mtid <- tryTakeMVar listenerThread | ||
195 | case mtid of | ||
196 | Nothing -> return () | ||
197 | Just tid -> killThread tid | ||
198 | |||
199 | -- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'. | ||
200 | withManager :: Options -> (Manager -> IO a) -> IO a | ||
201 | withManager opts = bracket (newManager opts) closeManager | ||
202 | |||
203 | {----------------------------------------------------------------------- | ||
204 | -- Exceptions | ||
205 | -----------------------------------------------------------------------} | ||
206 | |||
207 | data RpcException | ||
208 | -- | Unable to lookup hostname; | ||
209 | = HostUnknown | ||
210 | |||
211 | -- | Unable to lookup hostname; | ||
212 | | HostLookupFailed | ||
213 | |||
214 | -- | Expecting 'udp:', but some other scheme provided. | ||
215 | | UnrecognizedScheme String | ||
216 | |||
217 | -- | Tracker exists but not responding for specific number of seconds. | ||
218 | | TimeoutExpired Int | ||
219 | |||
220 | -- | Tracker responded with unexpected message type. | ||
221 | | UnexpectedResponse | ||
222 | { expectedMsg :: String | ||
223 | , actualMsg :: String | ||
224 | } | ||
225 | |||
226 | -- | RPC succeed, but tracker responded with error code. | ||
227 | | QueryFailed Text | ||
228 | |||
229 | -- | RPC manager closed while waiting for response. | ||
230 | | ManagerClosed | ||
231 | deriving (Eq, Show, Typeable) | ||
232 | |||
233 | instance Exception RpcException | ||
234 | |||
235 | {----------------------------------------------------------------------- | ||
236 | -- Host Addr resolution | ||
237 | -----------------------------------------------------------------------} | ||
238 | |||
239 | setPort :: PortNumber -> SockAddr -> SockAddr | ||
240 | setPort p (SockAddrInet _ h) = SockAddrInet p h | ||
241 | setPort p (SockAddrInet6 _ f h s) = SockAddrInet6 p f h s | ||
242 | setPort _ addr = addr | ||
243 | |||
244 | resolveURI :: URI -> IO SockAddr | ||
245 | resolveURI URI { uriAuthority = Just (URIAuth {..}) } = do | ||
246 | infos <- getAddrInfo Nothing (Just uriRegName) Nothing | ||
247 | let port = fromMaybe 0 (readMaybe (L.drop 1 uriPort) :: Maybe Int) | ||
248 | case infos of | ||
249 | AddrInfo {..} : _ -> return $ setPort (fromIntegral port) addrAddress | ||
250 | _ -> throwIO HostLookupFailed | ||
251 | resolveURI _ = throwIO HostUnknown | ||
252 | |||
253 | -- TODO caching? | ||
254 | getTrackerAddr :: Manager -> URI -> IO SockAddr | ||
255 | getTrackerAddr _ uri | ||
256 | | uriScheme uri == "udp:" = resolveURI uri | ||
257 | | otherwise = throwIO (UnrecognizedScheme (uriScheme uri)) | ||
258 | |||
259 | {----------------------------------------------------------------------- | ||
260 | Connection | ||
261 | -----------------------------------------------------------------------} | ||
262 | |||
263 | connectionLifetime :: NominalDiffTime | ||
264 | connectionLifetime = 60 | ||
265 | |||
266 | data Connection = Connection | ||
267 | { connectionId :: ConnectionId | ||
268 | , connectionTimestamp :: UTCTime | ||
269 | } deriving Show | ||
270 | |||
271 | -- placeholder for the first 'connect' | ||
272 | initialConnection :: Connection | ||
273 | initialConnection = Connection initialConnectionId (posixSecondsToUTCTime 0) | ||
274 | |||
275 | establishedConnection :: ConnectionId -> IO Connection | ||
276 | establishedConnection cid = Connection cid <$> getCurrentTime | ||
277 | |||
278 | isExpired :: Connection -> IO Bool | ||
279 | isExpired Connection {..} = do | ||
280 | currentTime <- getCurrentTime | ||
281 | let timeDiff = diffUTCTime currentTime connectionTimestamp | ||
282 | return $ timeDiff > connectionLifetime | ||
283 | |||
284 | {----------------------------------------------------------------------- | ||
285 | -- Transactions | ||
286 | -----------------------------------------------------------------------} | ||
287 | |||
288 | -- | Sometimes 'genTransactionId' may return already used transaction | ||
289 | -- id. We use a good entropy source but the issue /still/ (with very | ||
290 | -- small probabality) may happen. If the collision happen then this | ||
291 | -- function tries to find nearest unused slot, otherwise pending | ||
292 | -- transactions table is full. | ||
293 | firstUnused :: SockAddr -> TransactionId -> PendingQueries -> TransactionId | ||
294 | firstUnused addr rid m = do | ||
295 | case M.splitLookup rid <$> M.lookup addr m of | ||
296 | Nothing -> rid | ||
297 | Just (_ , Nothing, _ ) -> rid | ||
298 | Just (lt, Just _ , gt) -> | ||
299 | case backwardHole (keys lt) rid <|> forwardHole rid (keys gt) of | ||
300 | Nothing -> error "firstUnused: table is full" -- impossible | ||
301 | Just tid -> tid | ||
302 | where | ||
303 | forwardHole a [] | ||
304 | | a == maxBound = Nothing | ||
305 | | otherwise = Just (succ a) | ||
306 | forwardHole a (b : xs) | ||
307 | | succ a == b = forwardHole b xs | ||
308 | | otherwise = Just (succ a) | ||
309 | |||
310 | backwardHole [] a | ||
311 | | a == minBound = Nothing | ||
312 | | otherwise = Just (pred a) | ||
313 | backwardHole (b : xs) a | ||
314 | | b == pred a = backwardHole xs b | ||
315 | | otherwise = Just (pred a) | ||
316 | |||
317 | register :: SockAddr -> TransactionId -> PendingResponse | ||
318 | -> PendingQueries -> PendingQueries | ||
319 | register addr tid ares = M.alter insertId addr | ||
320 | where | ||
321 | insertId Nothing = Just (M.singleton tid ares) | ||
322 | insertId (Just m) = Just (M.insert tid ares m) | ||
323 | |||
324 | unregister :: SockAddr -> TransactionId | ||
325 | -> PendingQueries -> PendingQueries | ||
326 | unregister addr tid = M.update deleteId addr | ||
327 | where | ||
328 | deleteId m | ||
329 | | M.null m' = Nothing | ||
330 | | otherwise = Just m' | ||
331 | where | ||
332 | m' = M.delete tid m | ||
333 | |||
334 | -- | Generate a new unused transaction id and register as pending. | ||
335 | allocTransaction :: Manager -> SockAddr -> PendingResponse -> IO TransactionId | ||
336 | allocTransaction Manager {..} addr ares = | ||
337 | modifyMVar pendingResps $ \ m -> do | ||
338 | rndId <- genTransactionId | ||
339 | let tid = firstUnused addr rndId m | ||
340 | return (register addr tid ares m, tid) | ||
341 | |||
342 | -- | Wake up blocked thread and return response back. | ||
343 | commitTransaction :: Manager -> SockAddr -> TransactionId -> Response -> IO () | ||
344 | commitTransaction Manager {..} addr tid resp = | ||
345 | modifyMVarMasked_ pendingResps $ \ m -> do | ||
346 | case M.lookup tid =<< M.lookup addr m of | ||
347 | Nothing -> return m -- tracker responded after 'cancelTransaction' fired | ||
348 | Just ares -> do | ||
349 | putMVar ares (Right resp) | ||
350 | return $ unregister addr tid m | ||
351 | |||
352 | -- | Abort transaction forcefully. | ||
353 | cancelTransaction :: Manager -> SockAddr -> TransactionId -> IO () | ||
354 | cancelTransaction Manager {..} addr tid = | ||
355 | modifyMVarMasked_ pendingResps $ \m -> | ||
356 | return $ unregister addr tid m | ||
357 | |||
358 | -- | Handle responses from trackers. | ||
359 | listen :: Manager -> IO () | ||
360 | listen mgr @ Manager {..} = do | ||
361 | forever $ do | ||
362 | (bs, addr) <- BS.recvFrom sock (optMaxPacketSize options) | ||
363 | case decode bs of | ||
364 | Left _ -> return () -- parser failed, ignoring | ||
365 | Right (TransactionR {..}) -> commitTransaction mgr addr transIdR response | ||
366 | |||
367 | -- | Perform RPC transaction. If the action interrupted transaction | ||
368 | -- will be aborted. | ||
369 | transaction :: Manager -> SockAddr -> Connection -> Request -> IO Response | ||
370 | transaction mgr @ Manager {..} addr conn request = do | ||
371 | ares <- newEmptyMVar | ||
372 | tid <- allocTransaction mgr addr ares | ||
373 | performTransaction tid ares | ||
374 | `onException` cancelTransaction mgr addr tid | ||
375 | where | ||
376 | performTransaction tid ares = do | ||
377 | let trans = TransactionQ (connectionId conn) tid request | ||
378 | BS.sendAllTo sock (encode trans) addr | ||
379 | takeMVar ares >>= either throwIO return | ||
380 | |||
381 | {----------------------------------------------------------------------- | ||
382 | -- Connection cache | ||
383 | -----------------------------------------------------------------------} | ||
384 | |||
385 | connect :: Manager -> SockAddr -> Connection -> IO ConnectionId | ||
386 | connect m addr conn = do | ||
387 | resp <- transaction m addr conn Connect | ||
388 | case resp of | ||
389 | Connected cid -> return cid | ||
390 | Failed msg -> throwIO $ QueryFailed msg | ||
391 | _ -> throwIO $ UnexpectedResponse "connected" (responseName resp) | ||
392 | |||
393 | newConnection :: Manager -> SockAddr -> IO Connection | ||
394 | newConnection m addr = do | ||
395 | connId <- connect m addr initialConnection | ||
396 | establishedConnection connId | ||
397 | |||
398 | refreshConnection :: Manager -> SockAddr -> Connection -> IO Connection | ||
399 | refreshConnection mgr addr conn = do | ||
400 | expired <- isExpired conn | ||
401 | if expired | ||
402 | then do | ||
403 | connId <- connect mgr addr conn | ||
404 | establishedConnection connId | ||
405 | else do | ||
406 | return conn | ||
407 | |||
408 | withCache :: Manager -> SockAddr | ||
409 | -> (Maybe Connection -> IO Connection) -> IO Connection | ||
410 | withCache mgr addr action = do | ||
411 | cache <- readIORef (connectionCache mgr) | ||
412 | conn <- action (M.lookup addr cache) | ||
413 | writeIORef (connectionCache mgr) (M.insert addr conn cache) | ||
414 | return conn | ||
415 | |||
416 | getConnection :: Manager -> SockAddr -> IO Connection | ||
417 | getConnection mgr addr = withCache mgr addr $ | ||
418 | maybe (newConnection mgr addr) (refreshConnection mgr addr) | ||
419 | |||
420 | {----------------------------------------------------------------------- | ||
421 | -- RPC | ||
422 | -----------------------------------------------------------------------} | ||
423 | |||
424 | retransmission :: Options -> IO a -> IO a | ||
425 | retransmission Options {..} action = go optMinTimeout | ||
426 | where | ||
427 | go curTimeout | ||
428 | | curTimeout > optMaxTimeout = throwIO $ TimeoutExpired curTimeout | ||
429 | | otherwise = do | ||
430 | r <- timeout (curTimeout * sec) action | ||
431 | maybe (go (optMultiplier * curTimeout)) return r | ||
432 | |||
433 | queryTracker :: Manager -> URI -> Request -> IO Response | ||
434 | queryTracker mgr uri req = do | ||
435 | addr <- getTrackerAddr mgr uri | ||
436 | retransmission (options mgr) $ do | ||
437 | conn <- getConnection mgr addr | ||
438 | transaction mgr addr conn req | ||
439 | |||
440 | -- | This function can throw 'RpcException'. | ||
441 | announce :: Manager -> URI -> AnnounceQuery -> IO AnnounceInfo | ||
442 | announce mgr uri q = do | ||
443 | resp <- queryTracker mgr uri (Announce q) | ||
444 | case resp of | ||
445 | Announced info -> return info | ||
446 | _ -> throwIO $ UnexpectedResponse "announce" (responseName resp) | ||
447 | |||
448 | -- | This function can throw 'RpcException'. | ||
449 | scrape :: Manager -> URI -> ScrapeQuery -> IO ScrapeInfo | ||
450 | scrape mgr uri ihs = do | ||
451 | resp <- queryTracker mgr uri (Scrape ihs) | ||
452 | case resp of | ||
453 | Scraped info -> return $ L.zip ihs info | ||
454 | _ -> throwIO $ UnexpectedResponse "scrape" (responseName resp) | ||
diff --git a/bittorrent/src/Network/BitTorrent/Tracker/Session.hs b/bittorrent/src/Network/BitTorrent/Tracker/Session.hs new file mode 100644 index 00000000..aa4a832f --- /dev/null +++ b/bittorrent/src/Network/BitTorrent/Tracker/Session.hs | |||
@@ -0,0 +1,306 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2014 | ||
3 | -- License : BSD | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Multitracker sessions. | ||
9 | -- | ||
10 | {-# LANGUAGE FlexibleInstances #-} | ||
11 | {-# LANGUAGE TypeFamilies #-} | ||
12 | {-# LANGUAGE TypeSynonymInstances #-} | ||
13 | {-# LANGUAGE TemplateHaskell #-} | ||
14 | module Network.BitTorrent.Tracker.Session | ||
15 | ( -- * Session | ||
16 | Session | ||
17 | , Event (..) | ||
18 | , newSession | ||
19 | , closeSession | ||
20 | , withSession | ||
21 | |||
22 | -- * Client send notifications | ||
23 | , notify | ||
24 | , askPeers | ||
25 | |||
26 | -- * Session state | ||
27 | -- ** Status | ||
28 | , Status (..) | ||
29 | , getStatus | ||
30 | |||
31 | -- ** Single tracker sessions | ||
32 | , LastScrape (..) | ||
33 | , TrackerSession | ||
34 | , trackerPeers | ||
35 | , trackerScrape | ||
36 | , getSessionState | ||
37 | |||
38 | -- * Tracker Exchange | ||
39 | -- | BEP28: <http://www.bittorrent.org/beps/bep_0028.html> | ||
40 | , addTracker | ||
41 | , removeTracker | ||
42 | , getTrustedTrackers | ||
43 | ) where | ||
44 | |||
45 | import Control.Applicative | ||
46 | import Control.Exception | ||
47 | import Control.Concurrent | ||
48 | import Control.Concurrent.Chan.Split as CS | ||
49 | import Control.Monad | ||
50 | import Data.Default | ||
51 | import Data.Fixed | ||
52 | import Data.Foldable as F | ||
53 | import Data.IORef | ||
54 | import Data.List as L | ||
55 | import Data.Maybe | ||
56 | import Data.Time | ||
57 | import Data.Traversable | ||
58 | import Network.URI | ||
59 | |||
60 | import Data.Torrent | ||
61 | import Network.Address | ||
62 | import Network.BitTorrent.Internal.Cache | ||
63 | import Network.BitTorrent.Internal.Types | ||
64 | import Network.BitTorrent.Tracker.List as TL | ||
65 | import Network.BitTorrent.Tracker.Message | ||
66 | import Network.BitTorrent.Tracker.RPC as RPC | ||
67 | |||
68 | {----------------------------------------------------------------------- | ||
69 | -- Single tracker session | ||
70 | -----------------------------------------------------------------------} | ||
71 | |||
72 | -- | Status of this client. | ||
73 | data Status | ||
74 | = Running -- ^ This client is announced and listenning for incoming | ||
75 | -- connections. | ||
76 | | Paused -- ^ This client does not expecting incoming connections. | ||
77 | deriving (Show, Eq, Bounded, Enum) | ||
78 | |||
79 | -- | Client starting in the paused state. | ||
80 | instance Default Status where | ||
81 | def = Paused | ||
82 | |||
83 | -- | Tracker session starts with scrape unknown. | ||
84 | instance Default LastScrape where | ||
85 | def = LastScrape Nothing Nothing | ||
86 | |||
87 | data LastScrape = LastScrape | ||
88 | { -- | Count of leechers the tracker aware of. | ||
89 | scrapeLeechers :: Maybe Int | ||
90 | |||
91 | -- | Count of seeders the tracker aware of. | ||
92 | , scrapeSeeders :: Maybe Int | ||
93 | } deriving (Show, Eq) | ||
94 | |||
95 | -- | Single tracker session. | ||
96 | data TrackerSession = TrackerSession | ||
97 | { -- | Used to notify 'Stopped' and 'Completed' events. | ||
98 | statusSent :: !(Maybe Status) | ||
99 | |||
100 | -- | Can be used to retrieve peer set. | ||
101 | , trackerPeers :: Cached [PeerAddr IP] | ||
102 | |||
103 | -- | Can be used to show brief swarm stats in client GUI. | ||
104 | , trackerScrape :: Cached LastScrape | ||
105 | } | ||
106 | |||
107 | -- | Not contacted. | ||
108 | instance Default TrackerSession where | ||
109 | def = TrackerSession Nothing def def | ||
110 | |||
111 | -- | Do we need to notify this /specific/ tracker? | ||
112 | needNotify :: AnnounceEvent -> Maybe Status -> Maybe Bool | ||
113 | needNotify Started Nothing = Just True | ||
114 | needNotify Stopped Nothing = Just False | ||
115 | needNotify Completed Nothing = Just False | ||
116 | needNotify Started (Just Running) = Nothing | ||
117 | needNotify Stopped (Just Running) = Just True | ||
118 | needNotify Completed (Just Running) = Just True | ||
119 | needNotify Started (Just Paused ) = Just True | ||
120 | needNotify Stopped (Just Paused ) = Just False | ||
121 | needNotify Completed (Just Paused ) = Just True | ||
122 | |||
123 | -- | Client status after event announce succeed. | ||
124 | nextStatus :: AnnounceEvent -> Maybe Status | ||
125 | nextStatus Started = Just Running | ||
126 | nextStatus Stopped = Just Paused | ||
127 | nextStatus Completed = Nothing -- must keep previous status | ||
128 | |||
129 | seconds :: Int -> NominalDiffTime | ||
130 | seconds n = realToFrac (toEnum n :: Uni) | ||
131 | |||
132 | cachePeers :: AnnounceInfo -> IO (Cached [PeerAddr IP]) | ||
133 | cachePeers AnnounceInfo {..} = | ||
134 | newCached (seconds respInterval) | ||
135 | (seconds (fromMaybe respInterval respMinInterval)) | ||
136 | (getPeerList respPeers) | ||
137 | |||
138 | cacheScrape :: AnnounceInfo -> IO (Cached LastScrape) | ||
139 | cacheScrape AnnounceInfo {..} = | ||
140 | newCached (seconds respInterval) | ||
141 | (seconds (fromMaybe respInterval respMinInterval)) | ||
142 | LastScrape | ||
143 | { scrapeSeeders = respComplete | ||
144 | , scrapeLeechers = respIncomplete | ||
145 | } | ||
146 | |||
147 | -- | Make announce request to specific tracker returning new state. | ||
148 | notifyTo :: Manager -> Session -> AnnounceEvent | ||
149 | -> TierEntry TrackerSession -> IO TrackerSession | ||
150 | notifyTo mgr s @ Session {..} event (uri, entry @ TrackerSession {..}) = do | ||
151 | let shouldNotify = needNotify event statusSent | ||
152 | mustNotify <- maybe (isExpired trackerPeers) return shouldNotify | ||
153 | if not mustNotify | ||
154 | then return entry | ||
155 | else do | ||
156 | let q = SAnnounceQuery sessionTopic def Nothing (Just event) | ||
157 | res <- RPC.announce mgr uri q | ||
158 | when (statusSent == Nothing) $ do | ||
159 | send sessionEvents (TrackerConfirmed uri) | ||
160 | send sessionEvents (AnnouncedTo uri) | ||
161 | let status' = nextStatus event <|> statusSent | ||
162 | TrackerSession status' <$> cachePeers res <*> cacheScrape res | ||
163 | |||
164 | {----------------------------------------------------------------------- | ||
165 | -- Multitracker Session | ||
166 | -----------------------------------------------------------------------} | ||
167 | |||
168 | -- | Multitracker session. | ||
169 | data Session = Session | ||
170 | { -- | Infohash to announce at each 'announce' request. | ||
171 | sessionTopic :: !InfoHash | ||
172 | |||
173 | -- | Current status of this client is used to filter duplicated | ||
174 | -- notifications, for e.g. we don't want to notify a tracker with | ||
175 | -- ['Stopped', 'Stopped'], the last should be ignored. | ||
176 | , sessionStatus :: !(IORef Status) | ||
177 | |||
178 | -- | A set of single-tracker sessions. Any request to a tracker | ||
179 | -- must take a lock. | ||
180 | , sessionTrackers :: !(MVar (TrackerList TrackerSession)) | ||
181 | |||
182 | , sessionEvents :: !(SendPort (Event Session)) | ||
183 | } | ||
184 | |||
185 | instance EventSource Session where | ||
186 | data Event Session | ||
187 | = TrackerAdded URI | ||
188 | | TrackerConfirmed URI | ||
189 | | TrackerRemoved URI | ||
190 | | AnnouncedTo URI | ||
191 | | SessionClosed | ||
192 | |||
193 | listen Session {..} = CS.listen sessionEvents | ||
194 | |||
195 | |||
196 | -- | Create a new multitracker session in paused state. Tracker list | ||
197 | -- must contant only /trusted/ tracker uris. To start announcing | ||
198 | -- client presence use 'notify'. | ||
199 | newSession :: InfoHash -> TrackerList () -> IO Session | ||
200 | newSession ih origUris = do | ||
201 | urisList <- shuffleTiers origUris | ||
202 | statusRef <- newIORef def | ||
203 | entriesVar <- newMVar (fmap (const def) urisList) | ||
204 | eventStream <- newSendPort | ||
205 | return Session | ||
206 | { sessionTopic = ih | ||
207 | , sessionStatus = statusRef | ||
208 | , sessionTrackers = entriesVar | ||
209 | , sessionEvents = eventStream | ||
210 | } | ||
211 | |||
212 | -- | Release scarce resources associated with the given session. This | ||
213 | -- function block until all trackers tied with this peer notified with | ||
214 | -- 'Stopped' event. | ||
215 | closeSession :: Manager -> Session -> IO () | ||
216 | closeSession m s @ Session {..} = do | ||
217 | notify m s Stopped | ||
218 | send sessionEvents SessionClosed | ||
219 | |||
220 | {----------------------------------------------------------------------- | ||
221 | -- Operations | ||
222 | -----------------------------------------------------------------------} | ||
223 | |||
224 | -- | Normally you need to use 'Control.Monad.Trans.Resource.alloc'. | ||
225 | withSession :: Manager -> InfoHash -> TrackerList () | ||
226 | -> (Session -> IO ()) -> IO () | ||
227 | withSession m ih uris = bracket (newSession ih uris) (closeSession m) | ||
228 | |||
229 | -- | Get last announced status. The only action can alter this status | ||
230 | -- is 'notify'. | ||
231 | getStatus :: Session -> IO Status | ||
232 | getStatus Session {..} = readIORef sessionStatus | ||
233 | |||
234 | getSessionState :: Session -> IO [[TierEntry TrackerSession]] | ||
235 | getSessionState Session {..} = TL.toList <$> readMVar sessionTrackers | ||
236 | |||
237 | -- | Do we need to sent this event to a first working tracker or to | ||
238 | -- the all known good trackers? | ||
239 | allNotify :: AnnounceEvent -> Bool | ||
240 | allNotify Started = False | ||
241 | allNotify Stopped = True | ||
242 | allNotify Completed = True | ||
243 | |||
244 | notifyAll :: Manager -> Session -> AnnounceEvent -> IO () | ||
245 | notifyAll mgr s @ Session {..} event = do | ||
246 | modifyMVar_ sessionTrackers $ | ||
247 | (traversal (notifyTo mgr s event)) | ||
248 | where | ||
249 | traversal | ||
250 | | allNotify event = traverseAll | ||
251 | | otherwise = traverseTiers | ||
252 | |||
253 | -- TODO send notifications to tracker periodically. | ||
254 | -- | | ||
255 | -- | ||
256 | -- This function /may/ block until tracker query proceed. | ||
257 | notify :: Manager -> Session -> AnnounceEvent -> IO () | ||
258 | notify mgr ses event = do | ||
259 | prevStatus <- atomicModifyIORef (sessionStatus ses) $ \ s -> | ||
260 | (fromMaybe s (nextStatus event), s) | ||
261 | when (needNotify event (Just prevStatus) == Just True) $ do | ||
262 | notifyAll mgr ses event | ||
263 | |||
264 | -- TODO run announce if sesion have no peers | ||
265 | -- | The returned list of peers can have duplicates. | ||
266 | -- This function /may/ block. Use async if needed. | ||
267 | askPeers :: Manager -> Session -> IO [PeerAddr IP] | ||
268 | askPeers _mgr ses = do | ||
269 | list <- readMVar (sessionTrackers ses) | ||
270 | L.concat <$> collect (tryTakeData . trackerPeers) list | ||
271 | |||
272 | collect :: (a -> IO (Maybe b)) -> TrackerList a -> IO [b] | ||
273 | collect f lst = (catMaybes . F.toList) <$> traverse f lst | ||
274 | |||
275 | --sourcePeers :: Session -> Source (PeerAddr IP) | ||
276 | --sourcePeers | ||
277 | |||
278 | {----------------------------------------------------------------------- | ||
279 | -- Tracker exchange | ||
280 | -----------------------------------------------------------------------} | ||
281 | |||
282 | -- Trackers discovered through this protocol SHOULD be treated with a | ||
283 | -- certain amount of suspicion. Since the source of a tracker exchange | ||
284 | -- message cannot be trusted, an implementation SHOULD have a lower | ||
285 | -- number of retries before giving up entirely. | ||
286 | |||
287 | addTracker :: Session -> URI -> IO () | ||
288 | addTracker Session {..} uri = do | ||
289 | undefined | ||
290 | send sessionEvents (TrackerAdded uri) | ||
291 | |||
292 | removeTracker :: Manager -> Session -> URI -> IO () | ||
293 | removeTracker m Session {..} uri = do | ||
294 | send sessionEvents (TrackerRemoved uri) | ||
295 | |||
296 | -- Also, as specified under the definitions section, a tracker that | ||
297 | -- has not worked should never be propagated to other peers over the | ||
298 | -- tracker exchange protocol. | ||
299 | |||
300 | -- | Return all known trackers. | ||
301 | getTrackers :: Session -> IO [URI] | ||
302 | getTrackers = undefined | ||
303 | |||
304 | -- | Return trackers from torrent file and | ||
305 | getTrustedTrackers :: Session -> IO [URI] | ||
306 | getTrustedTrackers = undefined | ||
diff --git a/bittorrent/src/System/Torrent/FileMap.hs b/bittorrent/src/System/Torrent/FileMap.hs new file mode 100644 index 00000000..6e8d7f5a --- /dev/null +++ b/bittorrent/src/System/Torrent/FileMap.hs | |||
@@ -0,0 +1,151 @@ | |||
1 | {-# LANGUAGE RecordWildCards #-} | ||
2 | {-# LANGUAGE ViewPatterns #-} | ||
3 | {-# OPTIONS -fno-warn-orphans #-} | ||
4 | module System.Torrent.FileMap | ||
5 | ( FileMap | ||
6 | |||
7 | -- * Construction | ||
8 | , Mode (..) | ||
9 | , def | ||
10 | , mmapFiles | ||
11 | , unmapFiles | ||
12 | |||
13 | -- * Query | ||
14 | , System.Torrent.FileMap.size | ||
15 | |||
16 | -- * Modification | ||
17 | , readBytes | ||
18 | , writeBytes | ||
19 | , unsafeReadBytes | ||
20 | |||
21 | -- * Unsafe conversions | ||
22 | , fromLazyByteString | ||
23 | , toLazyByteString | ||
24 | ) where | ||
25 | |||
26 | import Control.Applicative | ||
27 | import Control.Monad as L | ||
28 | import Data.ByteString as BS | ||
29 | import Data.ByteString.Internal as BS | ||
30 | import Data.ByteString.Lazy as BL | ||
31 | import Data.ByteString.Lazy.Internal as BL | ||
32 | import Data.Default | ||
33 | import Data.Vector as V -- TODO use unboxed vector | ||
34 | import Foreign | ||
35 | import System.IO.MMap | ||
36 | |||
37 | import Data.Torrent | ||
38 | |||
39 | |||
40 | data FileEntry = FileEntry | ||
41 | { filePosition :: {-# UNPACK #-} !FileOffset | ||
42 | , fileBytes :: {-# UNPACK #-} !BS.ByteString | ||
43 | } deriving (Show, Eq) | ||
44 | |||
45 | type FileMap = Vector FileEntry | ||
46 | |||
47 | instance Default Mode where | ||
48 | def = ReadWriteEx | ||
49 | |||
50 | mmapFiles :: Mode -> FileLayout FileSize -> IO FileMap | ||
51 | mmapFiles mode layout = V.fromList <$> L.mapM mkEntry (accumPositions layout) | ||
52 | where | ||
53 | mkEntry (path, (pos, expectedSize)) = do | ||
54 | let esize = fromIntegral expectedSize -- FIXME does this safe? | ||
55 | (fptr, moff, msize) <- mmapFileForeignPtr path mode $ Just (0, esize) | ||
56 | if msize /= esize | ||
57 | then error "mmapFiles" -- TODO unmap mapped files on exception | ||
58 | else return $ FileEntry pos (PS fptr moff msize) | ||
59 | |||
60 | unmapFiles :: FileMap -> IO () | ||
61 | unmapFiles = V.mapM_ unmapEntry | ||
62 | where | ||
63 | unmapEntry (FileEntry _ (PS fptr _ _)) = finalizeForeignPtr fptr | ||
64 | |||
65 | fromLazyByteString :: BL.ByteString -> FileMap | ||
66 | fromLazyByteString lbs = V.unfoldr f (0, lbs) | ||
67 | where | ||
68 | f (_, Empty ) = Nothing | ||
69 | f (pos, Chunk x xs) = Just (FileEntry pos x, ((pos + chunkSize), xs)) | ||
70 | where chunkSize = fromIntegral $ BS.length x | ||
71 | |||
72 | -- | /O(n)/. | ||
73 | toLazyByteString :: FileMap -> BL.ByteString | ||
74 | toLazyByteString = V.foldr f Empty | ||
75 | where | ||
76 | f FileEntry {..} bs = Chunk fileBytes bs | ||
77 | |||
78 | -- | /O(1)/. | ||
79 | size :: FileMap -> FileOffset | ||
80 | size m | ||
81 | | V.null m = 0 | ||
82 | | FileEntry {..} <- V.unsafeLast m | ||
83 | = filePosition + fromIntegral (BS.length fileBytes) | ||
84 | |||
85 | bsearch :: FileOffset -> FileMap -> Maybe Int | ||
86 | bsearch x m | ||
87 | | V.null m = Nothing | ||
88 | | otherwise = branch (V.length m `div` 2) | ||
89 | where | ||
90 | branch c @ ((m !) -> FileEntry {..}) | ||
91 | | x < filePosition = bsearch x (V.take c m) | ||
92 | | x >= filePosition + fileSize = do | ||
93 | ix <- bsearch x (V.drop (succ c) m) | ||
94 | return $ succ c + ix | ||
95 | | otherwise = Just c | ||
96 | where | ||
97 | fileSize = fromIntegral (BS.length fileBytes) | ||
98 | |||
99 | -- | /O(log n)/. | ||
100 | drop :: FileOffset -> FileMap -> (FileSize, FileMap) | ||
101 | drop off m | ||
102 | | Just ix <- bsearch off m | ||
103 | , FileEntry {..} <- m ! ix = (off - filePosition, V.drop ix m) | ||
104 | | otherwise = (0 , V.empty) | ||
105 | |||
106 | -- | /O(log n)/. | ||
107 | take :: FileSize -> FileMap -> (FileMap, FileSize) | ||
108 | take len m | ||
109 | | len >= s = (m , 0) | ||
110 | | Just ix <- bsearch (pred len) m = let m' = V.take (succ ix) m | ||
111 | in (m', System.Torrent.FileMap.size m' - len) | ||
112 | | otherwise = (V.empty , 0) | ||
113 | where | ||
114 | s = System.Torrent.FileMap.size m | ||
115 | |||
116 | -- | /O(log n + m)/. Do not use this function with 'unmapFiles'. | ||
117 | unsafeReadBytes :: FileOffset -> FileSize -> FileMap -> BL.ByteString | ||
118 | unsafeReadBytes off s m | ||
119 | | (l , m') <- System.Torrent.FileMap.drop off m | ||
120 | , (m'', _ ) <- System.Torrent.FileMap.take (off + s) m' | ||
121 | = BL.take (fromIntegral s) $ BL.drop (fromIntegral l) $ toLazyByteString m'' | ||
122 | |||
123 | readBytes :: FileOffset -> FileSize -> FileMap -> IO BL.ByteString | ||
124 | readBytes off s m = do | ||
125 | let bs_copy = BL.copy $ unsafeReadBytes off s m | ||
126 | forceLBS bs_copy | ||
127 | return bs_copy | ||
128 | where | ||
129 | forceLBS Empty = return () | ||
130 | forceLBS (Chunk _ x) = forceLBS x | ||
131 | |||
132 | bscpy :: BL.ByteString -> BL.ByteString -> IO () | ||
133 | bscpy (PS _ _ 0 `Chunk` dest_rest) src = bscpy dest_rest src | ||
134 | bscpy dest (PS _ _ 0 `Chunk` src_rest) = bscpy dest src_rest | ||
135 | bscpy (PS dest_fptr dest_off dest_size `Chunk` dest_rest) | ||
136 | (PS src_fptr src_off src_size `Chunk` src_rest) | ||
137 | = do let csize = min dest_size src_size | ||
138 | withForeignPtr dest_fptr $ \dest_ptr -> | ||
139 | withForeignPtr src_fptr $ \src_ptr -> | ||
140 | memcpy (dest_ptr `advancePtr` dest_off) | ||
141 | (src_ptr `advancePtr` src_off) | ||
142 | (fromIntegral csize) -- TODO memmove? | ||
143 | bscpy (PS dest_fptr (dest_off + csize) (dest_size - csize) `Chunk` dest_rest) | ||
144 | (PS src_fptr (src_off + csize) (src_size - csize) `Chunk` src_rest) | ||
145 | bscpy _ _ = return () | ||
146 | |||
147 | writeBytes :: FileOffset -> BL.ByteString -> FileMap -> IO () | ||
148 | writeBytes off lbs m = bscpy dest src | ||
149 | where | ||
150 | src = BL.take (fromIntegral (BL.length dest)) lbs | ||
151 | dest = unsafeReadBytes off (fromIntegral (BL.length lbs)) m \ No newline at end of file | ||
diff --git a/bittorrent/src/System/Torrent/Storage.hs b/bittorrent/src/System/Torrent/Storage.hs new file mode 100644 index 00000000..1d77e55d --- /dev/null +++ b/bittorrent/src/System/Torrent/Storage.hs | |||
@@ -0,0 +1,221 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- This module implements mapping from single continious piece space | ||
9 | -- to file storage. Storage can be used in two modes: | ||
10 | -- | ||
11 | -- * As in memory storage - in this case we don't touch filesystem. | ||
12 | -- | ||
13 | -- * As ordinary mmaped file storage - when we need to store | ||
14 | -- data in the filesystem. | ||
15 | -- | ||
16 | {-# LANGUAGE RecordWildCards #-} | ||
17 | {-# LANGUAGE DeriveDataTypeable #-} | ||
18 | module System.Torrent.Storage | ||
19 | ( -- * Storage | ||
20 | Storage | ||
21 | , StorageFailure (..) | ||
22 | |||
23 | -- * Construction | ||
24 | , Mode (..) | ||
25 | , def | ||
26 | , open | ||
27 | , openInfoDict | ||
28 | , close | ||
29 | , withStorage | ||
30 | |||
31 | -- * Query | ||
32 | , totalPieces | ||
33 | , verifyPiece | ||
34 | , genPieceInfo | ||
35 | , getBitfield | ||
36 | |||
37 | -- * Modification | ||
38 | , writePiece | ||
39 | , readPiece | ||
40 | , hintRead | ||
41 | , unsafeReadPiece | ||
42 | |||
43 | -- * Streaming | ||
44 | , sourceStorage | ||
45 | , sinkStorage | ||
46 | ) where | ||
47 | |||
48 | import Control.Applicative | ||
49 | import Control.Exception | ||
50 | import Control.Monad as M | ||
51 | import Control.Monad.Trans | ||
52 | import Data.ByteString.Lazy as BL | ||
53 | import Data.Conduit as C | ||
54 | import Data.Conduit.Binary as C | ||
55 | import Data.Conduit.List as C | ||
56 | import Data.Typeable | ||
57 | |||
58 | import Data.Torrent | ||
59 | import Network.BitTorrent.Exchange.Bitfield as BF | ||
60 | import System.Torrent.FileMap as FM | ||
61 | |||
62 | |||
63 | -- | Some storage operations may throw an exception if misused. | ||
64 | data StorageFailure | ||
65 | -- | Occurs on a write operation if the storage has been opened | ||
66 | -- using 'ReadOnly' mode. | ||
67 | = StorageIsRO | ||
68 | |||
69 | -- | Piece index is out of bounds. | ||
70 | | InvalidIndex PieceIx | ||
71 | |||
72 | -- | Piece size do not match with one passed to the 'open' | ||
73 | -- function. | ||
74 | | InvalidSize PieceSize | ||
75 | deriving (Show, Eq, Typeable) | ||
76 | |||
77 | instance Exception StorageFailure | ||
78 | |||
79 | -- | Pieces store. | ||
80 | data Storage = Storage | ||
81 | { mode :: !Mode | ||
82 | , pieceLen :: {-# UNPACK #-} !PieceSize | ||
83 | , fileMap :: {-# UNPACK #-} !FileMap | ||
84 | } | ||
85 | |||
86 | -- | Map torrent files: | ||
87 | -- | ||
88 | -- * when torrent first created use 'ReadWriteEx' mode; | ||
89 | -- | ||
90 | -- * when seeding, validation 'ReadOnly' mode. | ||
91 | -- | ||
92 | open :: Mode -> PieceSize -> FileLayout FileSize -> IO Storage | ||
93 | open mode s l | ||
94 | | s <= 0 = throwIO (InvalidSize s) | ||
95 | | otherwise = Storage mode s <$> mmapFiles mode l | ||
96 | |||
97 | -- | Like 'open', but use 'InfoDict' file layout. | ||
98 | openInfoDict :: Mode -> FilePath -> InfoDict -> IO Storage | ||
99 | openInfoDict mode rootPath InfoDict {..} = | ||
100 | open mode (piPieceLength idPieceInfo) (flatLayout rootPath idLayoutInfo) | ||
101 | |||
102 | -- | Unmaps all files forcefully. It is recommended but not required. | ||
103 | close :: Storage -> IO () | ||
104 | close Storage {..} = unmapFiles fileMap | ||
105 | |||
106 | -- | Normally you need to use 'Control.Monad.Trans.Resource.allocate'. | ||
107 | withStorage :: Mode -> PieceSize -> FileLayout FileSize | ||
108 | -> (Storage -> IO ()) -> IO () | ||
109 | withStorage m s l = bracket (open m s l) close | ||
110 | |||
111 | -- TODO allocateStorage? | ||
112 | |||
113 | -- | Count of pieces in the storage. | ||
114 | totalPieces :: Storage -> PieceCount | ||
115 | totalPieces Storage {..} = FM.size fileMap `sizeInBase` pieceLen | ||
116 | |||
117 | isValidIx :: PieceIx -> Storage -> Bool | ||
118 | isValidIx i s = 0 <= i && i < totalPieces s | ||
119 | |||
120 | -- | Put piece data at the piece index by overwriting existing | ||
121 | -- data. | ||
122 | -- | ||
123 | -- This operation may throw 'StorageFailure'. | ||
124 | -- | ||
125 | writePiece :: Piece BL.ByteString -> Storage -> IO () | ||
126 | writePiece p @ Piece {..} s @ Storage {..} | ||
127 | | mode == ReadOnly = throwIO StorageIsRO | ||
128 | | isNotValidIx pieceIndex = throwIO (InvalidIndex pieceIndex) | ||
129 | | isNotValidSize pieceIndex (pieceSize p) | ||
130 | = throwIO (InvalidSize (pieceSize p)) | ||
131 | | otherwise = writeBytes offset pieceData fileMap | ||
132 | where | ||
133 | isNotValidSize pix psize | ||
134 | | succ pix == pcount = psize /= lastPieceLen -- last piece may be shorter | ||
135 | | otherwise = psize /= pieceLen | ||
136 | where | ||
137 | lastPieceLen = fromIntegral (FM.size fileMap `rem` fromIntegral pieceLen) | ||
138 | {-# INLINE isNotValidSize #-} | ||
139 | |||
140 | isNotValidIx i = i < 0 || i >= pcount | ||
141 | {-# INLINE isNotValidIx #-} | ||
142 | |||
143 | pcount = totalPieces s | ||
144 | offset = fromIntegral pieceIndex * fromIntegral pieceLen | ||
145 | |||
146 | -- | Read specific piece from storage. | ||
147 | -- | ||
148 | -- This operation may throw 'StorageFailure'. | ||
149 | -- | ||
150 | readPiece :: PieceIx -> Storage -> IO (Piece BL.ByteString) | ||
151 | readPiece pix s @ Storage {..} | ||
152 | | not (isValidIx pix s) = throwIO (InvalidIndex pix) | ||
153 | | otherwise = Piece pix <$> readBytes offset sz fileMap | ||
154 | where | ||
155 | offset = fromIntegral pix * fromIntegral pieceLen | ||
156 | sz = fromIntegral pieceLen | ||
157 | |||
158 | -- | Hint about the coming 'readPiece'. Ignores invalid indexes, for e.g.: | ||
159 | -- | ||
160 | -- @forall s. hindRead (-1) s == return ()@ | ||
161 | -- | ||
162 | hintRead :: PieceIx -> Storage -> IO () | ||
163 | hintRead _pix Storage {..} = return () | ||
164 | |||
165 | -- | Zero-copy version of readPiece. Can be used only with 'ReadOnly' | ||
166 | -- storages. | ||
167 | unsafeReadPiece :: PieceIx -> Storage -> IO (Piece BL.ByteString) | ||
168 | unsafeReadPiece pix s @ Storage {..} | ||
169 | | not (isValidIx pix s) = throwIO (InvalidIndex pix) | ||
170 | | otherwise = return $ Piece pix (unsafeReadBytes offset sz fileMap) | ||
171 | where | ||
172 | offset = fromIntegral pix * fromIntegral pieceLen | ||
173 | sz = fromIntegral pieceLen | ||
174 | |||
175 | -- | Stream storage pieces from first to the last. | ||
176 | sourceStorage :: Storage -> Source IO (Piece BL.ByteString) | ||
177 | sourceStorage s = go 0 | ||
178 | where | ||
179 | go pix | ||
180 | | pix < totalPieces s = do | ||
181 | piece <- liftIO $ readPiece pix s | ||
182 | liftIO $ hintRead (succ pix) s | ||
183 | yield piece | ||
184 | go (succ pix) | ||
185 | | otherwise = return () | ||
186 | |||
187 | -- | Write stream of pieces to the storage. Fail if storage is 'ReadOnly'. | ||
188 | sinkStorage :: Storage -> Sink (Piece BL.ByteString) IO () | ||
189 | sinkStorage s = do | ||
190 | awaitForever $ \ piece -> | ||
191 | liftIO $ writePiece piece s | ||
192 | |||
193 | -- | This function can be used to generate 'InfoDict' from a set of | ||
194 | -- opened files. | ||
195 | genPieceInfo :: Storage -> IO PieceInfo | ||
196 | genPieceInfo s = do | ||
197 | hashes <- sourceStorage s $= C.map hashPiece $$ C.sinkLbs | ||
198 | return $ PieceInfo (pieceLen s) (HashList (BL.toStrict hashes)) | ||
199 | |||
200 | -- | Verify specific piece using infodict hash list. | ||
201 | verifyPiece :: Storage -> PieceInfo -> PieceIx -> IO Bool | ||
202 | verifyPiece s pinfo pix = do | ||
203 | piece <- unsafeReadPiece pix s | ||
204 | return $! checkPieceLazy pinfo piece | ||
205 | |||
206 | -- | Verify storage. | ||
207 | -- | ||
208 | -- Throws 'InvalidSize' if piece info size do not match with storage | ||
209 | -- piece size. | ||
210 | -- | ||
211 | getBitfield :: Storage -> PieceInfo -> IO Bitfield | ||
212 | getBitfield s @ Storage {..} pinfo @ PieceInfo {..} | ||
213 | | pieceLen /= piPieceLength = throwIO (InvalidSize piPieceLength) | ||
214 | | otherwise = M.foldM checkPiece (BF.haveNone total) [0..total - 1] | ||
215 | where | ||
216 | total = totalPieces s | ||
217 | |||
218 | checkPiece :: Bitfield -> PieceIx -> IO Bitfield | ||
219 | checkPiece bf pix = do | ||
220 | valid <- verifyPiece s pinfo pix | ||
221 | return $ if valid then BF.insert pix bf else bf | ||
diff --git a/bittorrent/src/System/Torrent/Tree.hs b/bittorrent/src/System/Torrent/Tree.hs new file mode 100644 index 00000000..41cfb360 --- /dev/null +++ b/bittorrent/src/System/Torrent/Tree.hs | |||
@@ -0,0 +1,83 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Directory tree can be used to easily manipulate file layout info. | ||
9 | -- | ||
10 | {-# LANGUAGE FlexibleInstances #-} | ||
11 | {-# LANGUAGE TemplateHaskell #-} | ||
12 | {-# LANGUAGE DeriveDataTypeable #-} | ||
13 | module System.Torrent.Tree | ||
14 | ( -- * Directory tree | ||
15 | DirTree (..) | ||
16 | |||
17 | -- * Construction | ||
18 | , build | ||
19 | |||
20 | -- * Query | ||
21 | , System.Torrent.Tree.lookup | ||
22 | , lookupDir | ||
23 | , fileNumber | ||
24 | , dirNumber | ||
25 | ) where | ||
26 | |||
27 | import Data.ByteString as BS | ||
28 | import Data.ByteString.Char8 as BC | ||
29 | import Data.Foldable | ||
30 | import Data.List as L | ||
31 | import Data.Map as M | ||
32 | import Data.Monoid | ||
33 | |||
34 | import Data.Torrent | ||
35 | |||
36 | |||
37 | -- | 'DirTree' is more convenient form of 'LayoutInfo'. | ||
38 | data DirTree a = Dir { children :: Map ByteString (DirTree a) } | ||
39 | | File { node :: FileInfo a } | ||
40 | deriving Show | ||
41 | |||
42 | -- | Build directory tree from a list of files. | ||
43 | build :: LayoutInfo -> DirTree () | ||
44 | build SingleFile {liFile = FileInfo {..}} = Dir | ||
45 | { children = M.singleton fiName (File fi) } | ||
46 | where | ||
47 | fi = FileInfo fiLength fiMD5Sum () | ||
48 | build MultiFile {..} = Dir $ M.singleton liDirName files | ||
49 | where | ||
50 | files = Dir $ M.fromList $ L.map mkFileEntry liFiles | ||
51 | mkFileEntry FileInfo {..} = (L.head fiName, ent) -- TODO FIXME | ||
52 | where | ||
53 | ent = File $ FileInfo fiLength fiMD5Sum () | ||
54 | |||
55 | --decompress :: DirTree () -> [FileInfo ()] | ||
56 | --decompress = undefined | ||
57 | |||
58 | -- TODO pretty print | ||
59 | |||
60 | -- | Lookup file by path. | ||
61 | lookup :: [FilePath] -> DirTree a -> Maybe (DirTree a) | ||
62 | lookup [] t = Just t | ||
63 | lookup (p : ps) (Dir m) | Just subTree <- M.lookup (BC.pack p) m | ||
64 | = System.Torrent.Tree.lookup ps subTree | ||
65 | lookup _ _ = Nothing | ||
66 | |||
67 | -- | Lookup directory by path. | ||
68 | lookupDir :: [FilePath] -> DirTree a -> Maybe [(ByteString, DirTree a)] | ||
69 | lookupDir ps d = do | ||
70 | subTree <- System.Torrent.Tree.lookup ps d | ||
71 | case subTree of | ||
72 | File _ -> Nothing | ||
73 | Dir es -> Just $ M.toList es | ||
74 | |||
75 | -- | Get total count of files in directory and subdirectories. | ||
76 | fileNumber :: DirTree a -> Sum Int | ||
77 | fileNumber File {..} = Sum 1 | ||
78 | fileNumber Dir {..} = foldMap fileNumber children | ||
79 | |||
80 | -- | Get total count of directories in the directory and subdirectories. | ||
81 | dirNumber :: DirTree a -> Sum Int | ||
82 | dirNumber File {..} = Sum 0 | ||
83 | dirNumber Dir {..} = Sum 1 <> foldMap dirNumber children | ||