summaryrefslogtreecommitdiff
path: root/src/Data
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data')
-rw-r--r--src/Data/Bitfield.hs87
1 files changed, 86 insertions, 1 deletions
diff --git a/src/Data/Bitfield.hs b/src/Data/Bitfield.hs
index 1ceaf78b..3c278691 100644
--- a/src/Data/Bitfield.hs
+++ b/src/Data/Bitfield.hs
@@ -9,6 +9,21 @@
9-- bitfields. Bitfields are used to keep track indices of complete 9-- bitfields. Bitfields are used to keep track indices of complete
10-- pieces either peer have or client have. 10-- pieces either peer have or client have.
11-- 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-- * Random first - at the start.
17--
18-- * Rarest first selection - performed to avoid situation when
19-- rarest piece is unaccessible.
20--
21-- * _End game_ seletion - performed after a peer has requested all
22-- the subpieces of the content.
23--
24-- Note that BitTorrent applies the strict priority policy for
25-- /subpiece/ or /blocks/ selection.
26--
12{-# LANGUAGE CPP #-} 27{-# LANGUAGE CPP #-}
13{-# LANGUAGE BangPatterns #-} 28{-# LANGUAGE BangPatterns #-}
14{-# LANGUAGE RecordWildCards #-} 29{-# LANGUAGE RecordWildCards #-}
@@ -34,6 +49,13 @@ module Data.Bitfield
34 -- * Serialization 49 -- * Serialization
35 , fromBitmap, toBitmap 50 , fromBitmap, toBitmap
36 51
52 -- * Selection
53 , Selector
54 , selector, strategyClass
55
56 , strictFirst, strictLast
57 , rarestFirst, randomFirst, endGame
58
37#if defined (TESTING) 59#if defined (TESTING)
38 -- * Debug 60 -- * Debug
39 , mkBitfield 61 , mkBitfield
@@ -239,4 +261,67 @@ mkBitfield :: PieceCount -> [PieceIx] -> Bitfield
239mkBitfield s ixs = Bitfield { 261mkBitfield s ixs = Bitfield {
240 bfSize = s 262 bfSize = s
241 , bfSet = S.splitGT (-1) $ S.splitLT s $ S.fromList ixs 263 , bfSet = S.splitGT (-1) $ S.splitLT s $ S.fromList ixs
242 } \ No newline at end of file 264 }
265
266{-----------------------------------------------------------------------
267 Selection
268-----------------------------------------------------------------------}
269
270type Selector = Bitfield -- ^ Indices of client /have/ pieces.
271 -> Bitfield -- ^ Indices of peer /have/ pieces.
272 -> [Bitfield] -- ^ Indices of other peers /have/ pieces.
273 -> Maybe PieceIx -- ^ Zero-based index of piece to request
274 -- to, if any.
275
276selector :: Selector -- ^ Selector to use at the start.
277 -> Ratio PieceCount
278 -> Selector -- ^ Selector to use after the client have
279 -- the C pieces.
280 -> Selector -- ^ Selector that changes behaviour based
281 -- on completeness.
282selector start pt ready h a xs =
283 case strategyClass pt h of
284 SCBeginning -> start h a xs
285 SCReady -> ready h a xs
286 SCEnd -> endGame h a xs
287
288data StartegyClass
289 = SCBeginning
290 | SCReady
291 | SCEnd
292 deriving (Show, Eq, Ord, Enum, Bounded)
293
294
295strategyClass :: Ratio PieceCount -> Bitfield -> StartegyClass
296strategyClass threshold = classify . completeness
297 where
298 classify have
299 | have < threshold = SCBeginning
300 | have + 1 % numerator have < 1 = SCReady
301 -- FIXME numerator have is not total count
302 | otherwise = SCEnd
303
304
305-- | Select the first available piece.
306strictFirst :: Selector
307strictFirst h a _ = findMin (difference a h)
308
309-- | Select the last available piece.
310strictLast :: Selector
311strictLast h a _ = findMax (difference a h)
312
313-- |
314rarestFirst :: Selector
315rarestFirst h a xs = rarest (map (intersection want) xs)
316 where
317 want = difference h a
318
319-- | In average random first is faster than rarest first strategy but
320-- only if all pieces are available.
321randomFirst :: Selector
322randomFirst = do
323-- randomIO
324 error "randomFirst"
325
326endGame :: Selector
327endGame = strictLast