diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Network/BitTorrent.hs | 25 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange.hs | 45 | ||||
-rw-r--r-- | src/Network/BitTorrent/Internal.hs | 102 |
3 files changed, 132 insertions, 40 deletions
diff --git a/src/Network/BitTorrent.hs b/src/Network/BitTorrent.hs index 8a8879bb..ec0adb51 100644 --- a/src/Network/BitTorrent.hs +++ b/src/Network/BitTorrent.hs | |||
@@ -11,12 +11,12 @@ module Network.BitTorrent | |||
11 | module Data.Torrent | 11 | module Data.Torrent |
12 | 12 | ||
13 | -- * Session | 13 | -- * Session |
14 | -- ** Client | ||
15 | , ClientSession( clientPeerID, allowedExtensions ) | ||
16 | |||
17 | , ThreadCount | 14 | , ThreadCount |
18 | , defaultThreadCount | 15 | , defaultThreadCount |
19 | 16 | ||
17 | -- ** Client | ||
18 | , ClientSession( clientPeerID, allowedExtensions ) | ||
19 | |||
20 | , newClient | 20 | , newClient |
21 | , defaultClient | 21 | , defaultClient |
22 | 22 | ||
@@ -24,24 +24,37 @@ module Network.BitTorrent | |||
24 | , getPeerCount | 24 | , getPeerCount |
25 | , getSwarmCount | 25 | , getSwarmCount |
26 | 26 | ||
27 | |||
28 | -- ** Swarm | 27 | -- ** Swarm |
29 | , SwarmSession(torrentMeta) | 28 | , SwarmSession(torrentMeta) |
30 | , newLeacher, newSeeder | 29 | |
30 | , newLeecher | ||
31 | , newSeeder | ||
32 | |||
33 | , SessionCount | ||
31 | , getSessionCount | 34 | , getSessionCount |
32 | 35 | ||
33 | -- * Discovery | 36 | -- * Discovery |
34 | , discover | 37 | , discover |
35 | 38 | ||
36 | -- * Peer to Peer | 39 | -- * Peer to Peer |
37 | , PeerSession ( connectedPeerAddr, enabledExtensions ) | ||
38 | , P2P | 40 | , P2P |
39 | 41 | ||
42 | -- ** Session | ||
43 | , PeerSession( PeerSession, connectedPeerAddr | ||
44 | , swarmSession, enabledExtensions | ||
45 | ) | ||
46 | |||
47 | , getHaveCount | ||
48 | , getWantCount | ||
49 | , getPieceCount | ||
50 | |||
51 | |||
40 | -- ** Transfer | 52 | -- ** Transfer |
41 | , Block(..), ppBlock | 53 | , Block(..), ppBlock |
42 | , BlockIx(..), ppBlockIx | 54 | , BlockIx(..), ppBlockIx |
43 | 55 | ||
44 | -- ** Control | 56 | -- ** Control |
57 | , SessionException | ||
45 | , disconnect | 58 | , disconnect |
46 | , protocolError | 59 | , protocolError |
47 | 60 | ||
diff --git a/src/Network/BitTorrent/Exchange.hs b/src/Network/BitTorrent/Exchange.hs index 98b19357..9b5a8535 100644 --- a/src/Network/BitTorrent/Exchange.hs +++ b/src/Network/BitTorrent/Exchange.hs | |||
@@ -10,6 +10,7 @@ | |||
10 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 10 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
11 | {-# LANGUAGE MultiParamTypeClasses #-} | 11 | {-# LANGUAGE MultiParamTypeClasses #-} |
12 | {-# LANGUAGE RecordWildCards #-} | 12 | {-# LANGUAGE RecordWildCards #-} |
13 | {-# LANGUAGE FlexibleContexts #-} | ||
13 | module Network.BitTorrent.Exchange | 14 | module Network.BitTorrent.Exchange |
14 | ( -- * Block | 15 | ( -- * Block |
15 | Block(..), BlockIx(..) | 16 | Block(..), BlockIx(..) |
@@ -22,6 +23,10 @@ module Network.BitTorrent.Exchange | |||
22 | , awaitEvent, yieldEvent | 23 | , awaitEvent, yieldEvent |
23 | 24 | ||
24 | , disconnect, protocolError | 25 | , disconnect, protocolError |
26 | |||
27 | , getHaveCount | ||
28 | , getWantCount | ||
29 | , getPieceCount | ||
25 | ) where | 30 | ) where |
26 | 31 | ||
27 | import Control.Applicative | 32 | import Control.Applicative |
@@ -128,9 +133,12 @@ chainP2P :: SwarmSession -> PeerConnection -> P2P () -> IO () | |||
128 | Exceptions | 133 | Exceptions |
129 | -----------------------------------------------------------------------} | 134 | -----------------------------------------------------------------------} |
130 | 135 | ||
136 | -- | Terminate the current 'P2P' session. | ||
131 | disconnect :: MonadThrow m => m a | 137 | disconnect :: MonadThrow m => m a |
132 | disconnect = monadThrow PeerDisconnected | 138 | disconnect = monadThrow PeerDisconnected |
133 | 139 | ||
140 | -- TODO handle all protocol details here so we can hide this from | ||
141 | -- public interface | | ||
134 | protocolError :: MonadThrow m => Doc -> m a | 142 | protocolError :: MonadThrow m => Doc -> m a |
135 | protocolError = monadThrow . ProtocolError | 143 | protocolError = monadThrow . ProtocolError |
136 | 144 | ||
@@ -138,7 +146,40 @@ protocolError = monadThrow . ProtocolError | |||
138 | Helpers | 146 | Helpers |
139 | -----------------------------------------------------------------------} | 147 | -----------------------------------------------------------------------} |
140 | 148 | ||
141 | peerWant :: P2P Bitfield | 149 | -- | Count of client have pieces. |
150 | getHaveCount :: (MonadReader PeerSession m) => m PieceCount | ||
151 | getHaveCount = undefined | ||
152 | {-# INLINE getHaveCount #-} | ||
153 | |||
154 | -- | Count of client do not have pieces. | ||
155 | getWantCount :: (MonadReader PeerSession m) => m PieceCount | ||
156 | getWantCount = undefined | ||
157 | {-# INLINE getWantCount #-} | ||
158 | |||
159 | -- | Count of both have and want pieces. | ||
160 | getPieceCount :: (MonadReader PeerSession m) => m PieceCount | ||
161 | getPieceCount = asks findPieceCount | ||
162 | {-# INLINE getPieceCount #-} | ||
163 | |||
164 | -- for internal use only | ||
165 | emptyBF :: (MonadReader PeerSession m) => m Bitfield | ||
166 | emptyBF = liftM haveNone getPieceCount | ||
167 | |||
168 | fullBF :: (MonadReader PeerSession m) => m Bitfield | ||
169 | fullBF = liftM haveAll getPieceCount | ||
170 | |||
171 | singletonBF :: (MonadReader PeerSession m) => PieceIx -> m Bitfield | ||
172 | singletonBF i = liftM (BF.singleton i) getPieceCount | ||
173 | |||
174 | adjustBF :: (MonadReader PeerSession m) => Bitfield -> m Bitfield | ||
175 | adjustBF bf = (`adjustSize` bf) `liftM` getPieceCount | ||
176 | |||
177 | getClientBF :: (MonadIO m, MonadReader PeerSession m) => m Bitfield | ||
178 | getClientBF = asks swarmSession >>= liftIO . getClientBitfield | ||
179 | |||
180 | |||
181 | |||
182 | peerWant :: P2P Bitfield | ||
142 | peerWant = BF.difference <$> getClientBF <*> use bitfield | 183 | peerWant = BF.difference <$> getClientBF <*> use bitfield |
143 | 184 | ||
144 | clientWant :: P2P Bitfield | 185 | clientWant :: P2P Bitfield |
@@ -154,6 +195,8 @@ clientOffer = do | |||
154 | sessionStatus <- use status | 195 | sessionStatus <- use status |
155 | if canUpload sessionStatus then peerWant else emptyBF | 196 | if canUpload sessionStatus then peerWant else emptyBF |
156 | 197 | ||
198 | |||
199 | |||
157 | revise :: P2P Bitfield | 200 | revise :: P2P Bitfield |
158 | revise = do | 201 | revise = do |
159 | want <- clientWant | 202 | want <- clientWant |
diff --git a/src/Network/BitTorrent/Internal.hs b/src/Network/BitTorrent/Internal.hs index e07698dd..8ce7afbf 100644 --- a/src/Network/BitTorrent/Internal.hs +++ b/src/Network/BitTorrent/Internal.hs | |||
@@ -22,6 +22,7 @@ | |||
22 | {-# LANGUAGE FlexibleContexts #-} | 22 | {-# LANGUAGE FlexibleContexts #-} |
23 | {-# LANGUAGE MultiParamTypeClasses #-} | 23 | {-# LANGUAGE MultiParamTypeClasses #-} |
24 | {-# LANGUAGE UndecidableInstances #-} | 24 | {-# LANGUAGE UndecidableInstances #-} |
25 | {-# LANGUAGE ConstraintKinds #-} | ||
25 | module Network.BitTorrent.Internal | 26 | module Network.BitTorrent.Internal |
26 | ( Progress(..), startProgress | 27 | ( Progress(..), startProgress |
27 | 28 | ||
@@ -39,13 +40,21 @@ module Network.BitTorrent.Internal | |||
39 | 40 | ||
40 | 41 | ||
41 | -- * Swarm | 42 | -- * Swarm |
42 | , SwarmSession(SwarmSession, torrentMeta, clientSession) | 43 | , SwarmSession( SwarmSession, torrentMeta, clientSession ) |
44 | |||
45 | , SessionCount | ||
43 | , getSessionCount | 46 | , getSessionCount |
44 | , newLeacher, newSeeder | 47 | |
45 | , enterSwarm, leaveSwarm , waitVacancy | 48 | , newLeecher |
49 | , newSeeder | ||
50 | , getClientBitfield | ||
51 | |||
52 | , enterSwarm | ||
53 | , leaveSwarm | ||
54 | , waitVacancy | ||
46 | 55 | ||
47 | -- * Peer | 56 | -- * Peer |
48 | , PeerSession(PeerSession, connectedPeerAddr | 57 | , PeerSession( PeerSession, connectedPeerAddr |
49 | , swarmSession, enabledExtensions | 58 | , swarmSession, enabledExtensions |
50 | ) | 59 | ) |
51 | , SessionState | 60 | , SessionState |
@@ -58,8 +67,7 @@ module Network.BitTorrent.Internal | |||
58 | 67 | ||
59 | -- ** Properties | 68 | -- ** Properties |
60 | , bitfield, status | 69 | , bitfield, status |
61 | , emptyBF, fullBF, singletonBF, adjustBF | 70 | , findPieceCount |
62 | , getPieceCount, getClientBF | ||
63 | 71 | ||
64 | -- * Timeouts | 72 | -- * Timeouts |
65 | , updateIncoming, updateOutcoming | 73 | , updateIncoming, updateOutcoming |
@@ -237,7 +245,20 @@ newClient n exts = do | |||
237 | Swarm session | 245 | Swarm session |
238 | -----------------------------------------------------------------------} | 246 | -----------------------------------------------------------------------} |
239 | 247 | ||
240 | -- TODO document P2P sessions bounding | 248 | {- NOTE: If client is a leecher then there is NO particular reason to |
249 | set max sessions count more than the_number_of_unchoke_slots * k: | ||
250 | |||
251 | * thread slot(activeThread semaphore) | ||
252 | * will take but no | ||
253 | |||
254 | So if client is a leecher then max sessions count depends on the | ||
255 | number of unchoke slots. | ||
256 | |||
257 | However if client is a seeder then the value depends on . | ||
258 | -} | ||
259 | |||
260 | -- | Used to bound the number of simultaneous connections and, which | ||
261 | -- is the same, P2P sessions within the swarm session. | ||
241 | type SessionCount = Int | 262 | type SessionCount = Int |
242 | 263 | ||
243 | defSeederConns :: SessionCount | 264 | defSeederConns :: SessionCount |
@@ -271,10 +292,6 @@ instance Eq SwarmSession where | |||
271 | instance Ord SwarmSession where | 292 | instance Ord SwarmSession where |
272 | compare = comparing (tInfoHash . torrentMeta) | 293 | compare = comparing (tInfoHash . torrentMeta) |
273 | 294 | ||
274 | getSessionCount :: SwarmSession -> IO SessionCount | ||
275 | getSessionCount SwarmSession {..} = do | ||
276 | S.size <$> readTVarIO connectedPeers | ||
277 | |||
278 | newSwarmSession :: Int -> Bitfield -> ClientSession -> Torrent | 295 | newSwarmSession :: Int -> Bitfield -> ClientSession -> Torrent |
279 | -> IO SwarmSession | 296 | -> IO SwarmSession |
280 | newSwarmSession n bf cs @ ClientSession {..} t @ Torrent {..} | 297 | newSwarmSession n bf cs @ ClientSession {..} t @ Torrent {..} |
@@ -284,17 +301,27 @@ newSwarmSession n bf cs @ ClientSession {..} t @ Torrent {..} | |||
284 | <*> newTVarIO bf | 301 | <*> newTVarIO bf |
285 | <*> newTVarIO S.empty | 302 | <*> newTVarIO S.empty |
286 | 303 | ||
304 | -- | New swarm session in which the client allowed to upload only. | ||
287 | newSeeder :: ClientSession -> Torrent -> IO SwarmSession | 305 | newSeeder :: ClientSession -> Torrent -> IO SwarmSession |
288 | newSeeder cs t @ Torrent {..} | 306 | newSeeder cs t @ Torrent {..} |
289 | = newSwarmSession defSeederConns (haveAll (pieceCount tInfo)) cs t | 307 | = newSwarmSession defSeederConns (haveAll (pieceCount tInfo)) cs t |
290 | 308 | ||
291 | newLeacher :: ClientSession -> Torrent -> IO SwarmSession | 309 | -- | New swarm in which the client allowed both download and upload. |
292 | newLeacher cs t @ Torrent {..} | 310 | newLeecher :: ClientSession -> Torrent -> IO SwarmSession |
311 | newLeecher cs t @ Torrent {..} | ||
293 | = newSwarmSession defLeacherConns (haveNone (pieceCount tInfo)) cs t | 312 | = newSwarmSession defLeacherConns (haveNone (pieceCount tInfo)) cs t |
294 | 313 | ||
295 | --isLeacher :: SwarmSession -> IO Bool | 314 | --isLeacher :: SwarmSession -> IO Bool |
296 | --isLeacher = undefined | 315 | --isLeacher = undefined |
297 | 316 | ||
317 | -- | Get the number of connected peers in the given swarm. | ||
318 | getSessionCount :: SwarmSession -> IO SessionCount | ||
319 | getSessionCount SwarmSession {..} = do | ||
320 | S.size <$> readTVarIO connectedPeers | ||
321 | |||
322 | getClientBitfield :: SwarmSession -> IO Bitfield | ||
323 | getClientBitfield = readTVarIO . clientBitfield | ||
324 | |||
298 | {- | 325 | {- |
299 | haveDone :: MonadIO m => PieceIx -> SwarmSession -> m () | 326 | haveDone :: MonadIO m => PieceIx -> SwarmSession -> m () |
300 | haveDone ix = | 327 | haveDone ix = |
@@ -304,6 +331,8 @@ haveDone ix = | |||
304 | currentProgress | 331 | currentProgress |
305 | -} | 332 | -} |
306 | 333 | ||
334 | -- acquire/release mechanism: for internal use only | ||
335 | |||
307 | enterSwarm :: SwarmSession -> IO () | 336 | enterSwarm :: SwarmSession -> IO () |
308 | enterSwarm SwarmSession {..} = do | 337 | enterSwarm SwarmSession {..} = do |
309 | MSem.wait (activeThreads clientSession) | 338 | MSem.wait (activeThreads clientSession) |
@@ -323,11 +352,13 @@ waitVacancy se = | |||
323 | Peer session | 352 | Peer session |
324 | -----------------------------------------------------------------------} | 353 | -----------------------------------------------------------------------} |
325 | 354 | ||
355 | -- | Peer session contain all data necessary for peer to peer communication. | ||
326 | data PeerSession = PeerSession { | 356 | data PeerSession = PeerSession { |
327 | -- | Used as unique 'PeerSession' identifier within one | 357 | -- | Used as unique 'PeerSession' identifier within one |
328 | -- 'SwarmSession'. | 358 | -- 'SwarmSession'. |
329 | connectedPeerAddr :: !PeerAddr | 359 | connectedPeerAddr :: !PeerAddr |
330 | 360 | ||
361 | -- | The swarm to which both end points belong to. | ||
331 | , swarmSession :: !SwarmSession | 362 | , swarmSession :: !SwarmSession |
332 | 363 | ||
333 | -- | Extensions such that both peer and client support. | 364 | -- | Extensions such that both peer and client support. |
@@ -350,16 +381,24 @@ data PeerSession = PeerSession { | |||
350 | -- | 381 | -- |
351 | -- We should update timeout if we /send/ any message within timeout | 382 | -- We should update timeout if we /send/ any message within timeout |
352 | -- to avoid reduntant KA messages. | 383 | -- to avoid reduntant KA messages. |
384 | -- | ||
353 | , outcomingTimeout :: !TimeoutKey | 385 | , outcomingTimeout :: !TimeoutKey |
354 | 386 | ||
355 | -- TODO use dupChan for broadcasting | 387 | -- TODO use dupChan for broadcasting |
388 | |||
389 | -- | Channel used for replicate messages across all peers in | ||
390 | -- swarm. For exsample if we get some piece we should sent to all | ||
391 | -- connected (and interested in) peers HAVE message. | ||
392 | -- | ||
356 | , broadcastMessages :: !(Chan [Message]) | 393 | , broadcastMessages :: !(Chan [Message]) |
394 | |||
395 | -- | Dymanic P2P data. | ||
357 | , sessionState :: !(IORef SessionState) | 396 | , sessionState :: !(IORef SessionState) |
358 | } | 397 | } |
359 | 398 | ||
360 | data SessionState = SessionState { | 399 | data SessionState = SessionState { |
361 | _bitfield :: !Bitfield | 400 | _bitfield :: !Bitfield -- ^ Other peer Have bitfield. |
362 | , _status :: !SessionStatus | 401 | , _status :: !SessionStatus -- ^ Status of both peers. |
363 | } deriving (Show, Eq) | 402 | } deriving (Show, Eq) |
364 | 403 | ||
365 | $(makeLenses ''SessionState) | 404 | $(makeLenses ''SessionState) |
@@ -380,18 +419,28 @@ instance (MonadIO m, MonadReader PeerSession m) | |||
380 | 419 | ||
381 | put !s = asks sessionState >>= \ref -> liftIO $ writeIORef ref s | 420 | put !s = asks sessionState >>= \ref -> liftIO $ writeIORef ref s |
382 | 421 | ||
422 | |||
423 | -- | Exceptions used to interrupt the current P2P session. This | ||
424 | -- exceptions will NOT affect other P2P sessions, DHT, peer <-> | ||
425 | -- tracker, or any other session. | ||
426 | -- | ||
383 | data SessionException = PeerDisconnected | 427 | data SessionException = PeerDisconnected |
384 | | ProtocolError Doc | 428 | | ProtocolError Doc |
385 | deriving (Show, Typeable) | 429 | deriving (Show, Typeable) |
386 | 430 | ||
387 | instance Exception SessionException | 431 | instance Exception SessionException |
388 | 432 | ||
433 | |||
434 | -- | Do nothing with exception, used with 'handle' or 'try'. | ||
389 | isSessionException :: Monad m => SessionException -> m () | 435 | isSessionException :: Monad m => SessionException -> m () |
390 | isSessionException _ = return () | 436 | isSessionException _ = return () |
391 | 437 | ||
438 | -- | The same as 'isSessionException' but output to stdout the catched | ||
439 | -- exception, for debugging purposes only. | ||
392 | putSessionException :: SessionException -> IO () | 440 | putSessionException :: SessionException -> IO () |
393 | putSessionException = print | 441 | putSessionException = print |
394 | 442 | ||
443 | -- TODO modify such that we can use this in listener loop | ||
395 | -- TODO check if it connected yet peer | 444 | -- TODO check if it connected yet peer |
396 | withPeerSession :: SwarmSession -> PeerAddr | 445 | withPeerSession :: SwarmSession -> PeerAddr |
397 | -> ((Socket, PeerSession) -> IO ()) | 446 | -> ((Socket, PeerSession) -> IO ()) |
@@ -432,33 +481,20 @@ withPeerSession ss @ SwarmSession {..} addr | |||
432 | atomically $ modifyTVar' connectedPeers (S.delete ps) | 481 | atomically $ modifyTVar' connectedPeers (S.delete ps) |
433 | close sock | 482 | close sock |
434 | 483 | ||
435 | getPieceCount :: (MonadReader PeerSession m) => m PieceCount | 484 | findPieceCount :: PeerSession -> PieceCount |
436 | getPieceCount = asks (pieceCount . tInfo . torrentMeta . swarmSession) | 485 | findPieceCount = pieceCount . tInfo . torrentMeta . swarmSession |
437 | |||
438 | emptyBF :: (MonadReader PeerSession m) => m Bitfield | ||
439 | emptyBF = liftM haveNone getPieceCount | ||
440 | |||
441 | fullBF :: (MonadReader PeerSession m) => m Bitfield | ||
442 | fullBF = liftM haveAll getPieceCount | ||
443 | |||
444 | singletonBF :: (MonadReader PeerSession m) => PieceIx -> m Bitfield | ||
445 | singletonBF i = liftM (BF.singleton i) getPieceCount | ||
446 | |||
447 | adjustBF :: (MonadReader PeerSession m) => Bitfield -> m Bitfield | ||
448 | adjustBF bf = (`adjustSize` bf) `liftM` getPieceCount | ||
449 | |||
450 | getClientBF :: (MonadIO m, MonadReader PeerSession m) => m Bitfield | ||
451 | getClientBF = asks swarmSession >>= liftIO . readTVarIO . clientBitfield | ||
452 | 486 | ||
487 | -- TODO use this type for broadcast messages instead of 'Message' | ||
453 | --data Signal = | 488 | --data Signal = |
454 | --nextBroadcast :: P2P (Maybe Signal) | 489 | --nextBroadcast :: P2P (Maybe Signal) |
455 | --nextBroadcast = | 490 | --nextBroadcast = |
456 | 491 | ||
457 | |||
458 | {----------------------------------------------------------------------- | 492 | {----------------------------------------------------------------------- |
459 | Timeouts | 493 | Timeouts |
460 | -----------------------------------------------------------------------} | 494 | -----------------------------------------------------------------------} |
461 | 495 | ||
496 | -- for internal use only | ||
497 | |||
462 | sec :: Int | 498 | sec :: Int |
463 | sec = 1000 * 1000 | 499 | sec = 1000 * 1000 |
464 | 500 | ||