summaryrefslogtreecommitdiff
path: root/bittorrent/src/Network/BitTorrent/Exchange/Bitfield.hs
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-09-15 06:22:10 -0400
committerjoe <joe@jerkface.net>2017-09-15 06:22:10 -0400
commit12cbb3af2413dc28838ed271351dda16df8f7bdb (patch)
tree2db77a787e18a81a8369a8d73fee369d8826f064 /bittorrent/src/Network/BitTorrent/Exchange/Bitfield.hs
parent362357c6d08cbd8dffa627a1e80199dcb9ba231f (diff)
Separating dht-client library from bittorrent package.
Diffstat (limited to 'bittorrent/src/Network/BitTorrent/Exchange/Bitfield.hs')
-rw-r--r--bittorrent/src/Network/BitTorrent/Exchange/Bitfield.hs399
1 files changed, 399 insertions, 0 deletions
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 #-}
31module 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
92import Control.Monad
93import Control.Monad.ST
94import Data.ByteString (ByteString)
95import qualified Data.ByteString as B
96import qualified Data.ByteString.Lazy as Lazy
97import Data.Vector.Unboxed (Vector)
98import qualified Data.Vector.Unboxed as V
99import qualified Data.Vector.Unboxed.Mutable as VM
100import Data.IntervalSet (IntSet)
101import qualified Data.IntervalSet as S
102import qualified Data.IntervalSet.ByteString as S
103import Data.List (foldl')
104import Data.Monoid
105import Data.Ratio
106
107import 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--
117data 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
124instance 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.
135haveNone :: PieceCount -> Bitfield
136haveNone s = Bitfield s S.empty
137
138-- | The full bitfield containing all piece indices for the given size.
139haveAll :: PieceCount -> Bitfield
140haveAll s = Bitfield s (S.interval 0 (s - 1))
141
142-- | Insert the index in the set ignoring out of range indices.
143have :: PieceIx -> Bitfield -> Bitfield
144have ix Bitfield {..}
145 | 0 <= ix && ix < bfSize = Bitfield bfSize (S.insert ix bfSet)
146 | otherwise = Bitfield bfSize bfSet
147
148singleton :: PieceIx -> PieceCount -> Bitfield
149singleton ix pc = have ix (haveNone pc)
150
151-- | Assign new size to bitfield. FIXME Normally, size should be only
152-- decreased, otherwise exception raised.
153adjustSize :: PieceCount -> Bitfield -> Bitfield
154adjustSize s Bitfield {..} = Bitfield s bfSet
155
156-- | NOTE: for internal use only
157interval :: PieceCount -> PieceIx -> PieceIx -> Bitfield
158interval 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.
165null :: Bitfield -> Bool
166null Bitfield {..} = S.null bfSet
167
168-- | Test if bitfield have all pieces.
169full :: Bitfield -> Bool
170full Bitfield {..} = S.size bfSet == bfSize
171
172-- | Count of peer have pieces.
173haveCount :: Bitfield -> PieceCount
174haveCount = S.size . bfSet
175
176-- | Total count of pieces and its indices.
177totalCount :: Bitfield -> PieceCount
178totalCount = bfSize
179
180-- | Ratio of /have/ piece count to the /total/ piece count.
181--
182-- > forall bf. 0 <= completeness bf <= 1
183--
184completeness :: Bitfield -> Ratio PieceCount
185completeness b = haveCount b % totalCount b
186
187inRange :: PieceIx -> Bitfield -> Bool
188inRange ix Bitfield {..} = 0 <= ix && ix < bfSize
189
190member :: PieceIx -> Bitfield -> Bool
191member ix bf @ Bitfield {..}
192 | ix `inRange` bf = ix `S.member` bfSet
193 | otherwise = False
194
195notMember :: PieceIx -> Bitfield -> Bool
196notMember ix bf @ Bitfield {..}
197 | ix `inRange` bf = ix `S.notMember` bfSet
198 | otherwise = True
199
200-- | Find first available piece index.
201findMin :: Bitfield -> PieceIx
202findMin = S.findMin . bfSet
203{-# INLINE findMin #-}
204
205-- | Find last available piece index.
206findMax :: Bitfield -> PieceIx
207findMax = S.findMax . bfSet
208{-# INLINE findMax #-}
209
210-- | Check if all pieces from first bitfield present if the second bitfield
211isSubsetOf :: Bitfield -> Bitfield -> Bool
212isSubsetOf a b = bfSet a `S.isSubsetOf` bfSet b
213{-# INLINE isSubsetOf #-}
214
215-- | Resulting bitfield includes only missing pieces.
216complement :: Bitfield -> Bitfield
217complement 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.
232type Frequency = Int
233
234-- TODO rename to availability
235-- | How many times each piece index occur in the given bitfield set.
236frequencies :: [Bitfield] -> Vector Frequency
237frequencies [] = V.fromList []
238frequencies 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'.
253rarest :: [Bitfield] -> Maybe PieceIx
254rarest 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
273insert :: PieceIx -> Bitfield -> Bitfield
274insert 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.
282union :: Bitfield -> Bitfield -> Bitfield
283union 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.
289intersection :: Bitfield -> Bitfield -> Bitfield
290intersection 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.
296difference :: Bitfield -> Bitfield -> Bitfield
297difference 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.
303unions :: [Bitfield] -> Bitfield
304unions = {-# SCC unions #-} foldl' union (haveNone 0)
305
306{-----------------------------------------------------------------------
307 Serialization
308-----------------------------------------------------------------------}
309
310-- | List all /have/ indexes.
311toList :: Bitfield -> [PieceIx]
312toList Bitfield {..} = S.toList bfSet
313
314-- | Make bitfield from list of /have/ indexes.
315fromList :: PieceCount -> [PieceIx] -> Bitfield
316fromList 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'.
323fromBitmap :: ByteString -> Bitfield
324fromBitmap 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.
331toBitmap :: Bitfield -> Lazy.ByteString
332toBitmap 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
342type 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
348selector :: 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.
354selector 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
360data StartegyClass
361 = SCBeginning
362 | SCReady
363 | SCEnd
364 deriving (Show, Eq, Ord, Enum, Bounded)
365
366
367strategyClass :: Ratio PieceCount -> Bitfield -> StartegyClass
368strategyClass 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.
378strictFirst :: Selector
379strictFirst h a _ = Just $ findMin (difference a h)
380
381-- | Select the last available piece.
382strictLast :: Selector
383strictLast h a _ = Just $ findMax (difference a h)
384
385-- |
386rarestFirst :: Selector
387rarestFirst 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.
393randomFirst :: Selector
394randomFirst = do
395-- randomIO
396 error "randomFirst"
397
398endGame :: Selector
399endGame = strictLast