diff options
author | Sam Truzjan <pxqr.sta@gmail.com> | 2014-04-26 07:42:57 +0400 |
---|---|---|
committer | Sam Truzjan <pxqr.sta@gmail.com> | 2014-04-26 07:42:57 +0400 |
commit | a7fda9d39ed82cb9d3ad0c28e76e88e59539a492 (patch) | |
tree | 925183a691bbb57ca5f7140614e1fdbc610b3b1e /src/Network/BitTorrent/Exchange/Bitfield.hs | |
parent | 4587ffd5406162bb06a6549ffd2ff277e0a93916 (diff) | |
parent | 85bf8475bbbce79b1bedde641192fa945614283d (diff) |
Merge branch 'tidy' into dev
Diffstat (limited to 'src/Network/BitTorrent/Exchange/Bitfield.hs')
-rw-r--r-- | src/Network/BitTorrent/Exchange/Bitfield.hs | 398 |
1 files changed, 398 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/Exchange/Bitfield.hs b/src/Network/BitTorrent/Exchange/Bitfield.hs new file mode 100644 index 00000000..eca11d83 --- /dev/null +++ b/src/Network/BitTorrent/Exchange/Bitfield.hs | |||
@@ -0,0 +1,398 @@ | |||
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 peer have or client 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 | -- * 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 | -- | ||
27 | {-# LANGUAGE CPP #-} | ||
28 | {-# LANGUAGE BangPatterns #-} | ||
29 | {-# LANGUAGE RecordWildCards #-} | ||
30 | module Network.BitTorrent.Exchange.Bitfield | ||
31 | ( -- * Bitfield | ||
32 | PieceIx | ||
33 | , PieceCount | ||
34 | , Bitfield | ||
35 | |||
36 | -- * Construction | ||
37 | , haveAll | ||
38 | , haveNone | ||
39 | , have | ||
40 | , singleton | ||
41 | , interval | ||
42 | , adjustSize | ||
43 | |||
44 | -- * Query | ||
45 | -- ** Cardinality | ||
46 | , Network.BitTorrent.Exchange.Bitfield.null | ||
47 | , Network.BitTorrent.Exchange.Bitfield.full | ||
48 | , haveCount | ||
49 | , totalCount | ||
50 | , completeness | ||
51 | |||
52 | -- ** Membership | ||
53 | , member | ||
54 | , notMember | ||
55 | , findMin | ||
56 | , findMax | ||
57 | , isSubsetOf | ||
58 | |||
59 | -- ** Availability | ||
60 | , complement | ||
61 | , Frequency | ||
62 | , frequencies | ||
63 | , rarest | ||
64 | |||
65 | -- * Combine | ||
66 | , insert | ||
67 | , union | ||
68 | , intersection | ||
69 | , difference | ||
70 | |||
71 | -- * Conversion | ||
72 | , toList | ||
73 | , fromList | ||
74 | |||
75 | -- * Serialization | ||
76 | , fromBitmap | ||
77 | , toBitmap | ||
78 | |||
79 | -- * Piece selection | ||
80 | , Selector | ||
81 | , selector | ||
82 | , strategyClass | ||
83 | |||
84 | , strictFirst | ||
85 | , strictLast | ||
86 | , rarestFirst | ||
87 | , randomFirst | ||
88 | , endGame | ||
89 | ) where | ||
90 | |||
91 | import Control.Monad | ||
92 | import Control.Monad.ST | ||
93 | import Data.ByteString (ByteString) | ||
94 | import qualified Data.ByteString as B | ||
95 | import qualified Data.ByteString.Lazy as Lazy | ||
96 | import Data.Vector.Unboxed (Vector) | ||
97 | import qualified Data.Vector.Unboxed as V | ||
98 | import qualified Data.Vector.Unboxed.Mutable as VM | ||
99 | import Data.IntervalSet (IntSet) | ||
100 | import qualified Data.IntervalSet as S | ||
101 | import qualified Data.IntervalSet.ByteString as S | ||
102 | import Data.List (foldl') | ||
103 | import Data.Monoid | ||
104 | import Data.Ratio | ||
105 | |||
106 | import Data.Torrent | ||
107 | |||
108 | -- TODO cache some operations | ||
109 | |||
110 | -- | Bitfields are represented just as integer sets but with | ||
111 | -- restriction: the each set should be within given interval (or | ||
112 | -- subset of the specified interval). Size is used to specify | ||
113 | -- interval, so bitfield of size 10 might contain only indices in | ||
114 | -- interval [0..9]. | ||
115 | -- | ||
116 | data Bitfield = Bitfield { | ||
117 | bfSize :: !PieceCount | ||
118 | , bfSet :: !IntSet | ||
119 | } deriving (Show, Read, Eq) | ||
120 | |||
121 | -- Invariants: all elements of bfSet lie in [0..bfSize - 1]; | ||
122 | |||
123 | instance Monoid Bitfield where | ||
124 | {-# SPECIALIZE instance Monoid Bitfield #-} | ||
125 | mempty = haveNone 0 | ||
126 | mappend = union | ||
127 | mconcat = unions | ||
128 | |||
129 | {----------------------------------------------------------------------- | ||
130 | Construction | ||
131 | -----------------------------------------------------------------------} | ||
132 | |||
133 | -- | The empty bitfield of the given size. | ||
134 | haveNone :: PieceCount -> Bitfield | ||
135 | haveNone s = Bitfield s S.empty | ||
136 | |||
137 | -- | The full bitfield containing all piece indices for the given size. | ||
138 | haveAll :: PieceCount -> Bitfield | ||
139 | haveAll s = Bitfield s (S.interval 0 (s - 1)) | ||
140 | |||
141 | -- | Insert the index in the set ignoring out of range indices. | ||
142 | have :: PieceIx -> Bitfield -> Bitfield | ||
143 | have ix Bitfield {..} | ||
144 | | 0 <= ix && ix < bfSize = Bitfield bfSize (S.insert ix bfSet) | ||
145 | | otherwise = Bitfield bfSize bfSet | ||
146 | |||
147 | singleton :: PieceIx -> PieceCount -> Bitfield | ||
148 | singleton ix pc = have ix (haveNone pc) | ||
149 | |||
150 | -- | Assign new size to bitfield. FIXME Normally, size should be only | ||
151 | -- decreased, otherwise exception raised. | ||
152 | adjustSize :: PieceCount -> Bitfield -> Bitfield | ||
153 | adjustSize s Bitfield {..} = Bitfield s bfSet | ||
154 | |||
155 | -- | NOTE: for internal use only | ||
156 | interval :: PieceCount -> PieceIx -> PieceIx -> Bitfield | ||
157 | interval pc a b = Bitfield pc (S.interval a b) | ||
158 | |||
159 | {----------------------------------------------------------------------- | ||
160 | Query | ||
161 | -----------------------------------------------------------------------} | ||
162 | |||
163 | -- | Test if bitifield have no one index: peer do not have anything. | ||
164 | null :: Bitfield -> Bool | ||
165 | null Bitfield {..} = S.null bfSet | ||
166 | |||
167 | -- | Test if bitfield have all pieces. | ||
168 | full :: Bitfield -> Bool | ||
169 | full Bitfield {..} = S.size bfSet == bfSize | ||
170 | |||
171 | -- | Count of peer have pieces. | ||
172 | haveCount :: Bitfield -> PieceCount | ||
173 | haveCount = S.size . bfSet | ||
174 | |||
175 | -- | Total count of pieces and its indices. | ||
176 | totalCount :: Bitfield -> PieceCount | ||
177 | totalCount = bfSize | ||
178 | |||
179 | -- | Ratio of /have/ piece count to the /total/ piece count. | ||
180 | -- | ||
181 | -- > forall bf. 0 <= completeness bf <= 1 | ||
182 | -- | ||
183 | completeness :: Bitfield -> Ratio PieceCount | ||
184 | completeness b = haveCount b % totalCount b | ||
185 | |||
186 | inRange :: PieceIx -> Bitfield -> Bool | ||
187 | inRange ix Bitfield {..} = 0 <= ix && ix < bfSize | ||
188 | |||
189 | member :: PieceIx -> Bitfield -> Bool | ||
190 | member ix bf @ Bitfield {..} | ||
191 | | ix `inRange` bf = ix `S.member` bfSet | ||
192 | | otherwise = False | ||
193 | |||
194 | notMember :: PieceIx -> Bitfield -> Bool | ||
195 | notMember ix bf @ Bitfield {..} | ||
196 | | ix `inRange` bf = ix `S.notMember` bfSet | ||
197 | | otherwise = True | ||
198 | |||
199 | -- | Find first available piece index. | ||
200 | findMin :: Bitfield -> PieceIx | ||
201 | findMin = S.findMin . bfSet | ||
202 | {-# INLINE findMin #-} | ||
203 | |||
204 | -- | Find last available piece index. | ||
205 | findMax :: Bitfield -> PieceIx | ||
206 | findMax = S.findMax . bfSet | ||
207 | {-# INLINE findMax #-} | ||
208 | |||
209 | -- | Check if all pieces from first bitfield present if the second bitfield | ||
210 | isSubsetOf :: Bitfield -> Bitfield -> Bool | ||
211 | isSubsetOf a b = bfSet a `S.isSubsetOf` bfSet b | ||
212 | {-# INLINE isSubsetOf #-} | ||
213 | |||
214 | -- | Resulting bitfield includes only missing pieces. | ||
215 | complement :: Bitfield -> Bitfield | ||
216 | complement Bitfield {..} = Bitfield | ||
217 | { bfSet = uni `S.difference` bfSet | ||
218 | , bfSize = bfSize | ||
219 | } | ||
220 | where | ||
221 | Bitfield _ uni = haveAll bfSize | ||
222 | {-# INLINE complement #-} | ||
223 | |||
224 | {----------------------------------------------------------------------- | ||
225 | -- Availability | ||
226 | -----------------------------------------------------------------------} | ||
227 | |||
228 | -- | Frequencies are needed in piece selection startegies which use | ||
229 | -- availability quantity to find out the optimal next piece index to | ||
230 | -- download. | ||
231 | type Frequency = Int | ||
232 | |||
233 | -- TODO rename to availability | ||
234 | -- | How many times each piece index occur in the given bitfield set. | ||
235 | frequencies :: [Bitfield] -> Vector Frequency | ||
236 | frequencies [] = V.fromList [] | ||
237 | frequencies xs = runST $ do | ||
238 | v <- VM.new size | ||
239 | VM.set v 0 | ||
240 | forM_ xs $ \ Bitfield {..} -> do | ||
241 | forM_ (S.toList bfSet) $ \ x -> do | ||
242 | fr <- VM.read v x | ||
243 | VM.write v x (succ fr) | ||
244 | V.unsafeFreeze v | ||
245 | where | ||
246 | size = maximum (map bfSize xs) | ||
247 | |||
248 | -- TODO it seems like this operation is veeery slow | ||
249 | |||
250 | -- | Find least available piece index. If no piece available return | ||
251 | -- 'Nothing'. | ||
252 | rarest :: [Bitfield] -> Maybe PieceIx | ||
253 | rarest xs | ||
254 | | V.null freqMap = Nothing | ||
255 | | otherwise | ||
256 | = Just $ fst $ V.ifoldr' minIx (0, freqMap V.! 0) freqMap | ||
257 | where | ||
258 | freqMap = frequencies xs | ||
259 | |||
260 | minIx :: PieceIx -> Frequency | ||
261 | -> (PieceIx, Frequency) | ||
262 | -> (PieceIx, Frequency) | ||
263 | minIx ix fr acc@(_, fra) | ||
264 | | fr < fra && fr > 0 = (ix, fr) | ||
265 | | otherwise = acc | ||
266 | |||
267 | |||
268 | {----------------------------------------------------------------------- | ||
269 | Combine | ||
270 | -----------------------------------------------------------------------} | ||
271 | |||
272 | insert :: PieceIx -> Bitfield -> Bitfield | ||
273 | insert pix bf @ Bitfield {..} | ||
274 | | 0 <= pix && pix < bfSize = Bitfield | ||
275 | { bfSet = S.insert pix bfSet | ||
276 | , bfSize = bfSize | ||
277 | } | ||
278 | | otherwise = bf | ||
279 | |||
280 | -- | Find indices at least one peer have. | ||
281 | union :: Bitfield -> Bitfield -> Bitfield | ||
282 | union a b = {-# SCC union #-} Bitfield { | ||
283 | bfSize = bfSize a `max` bfSize b | ||
284 | , bfSet = bfSet a `S.union` bfSet b | ||
285 | } | ||
286 | |||
287 | -- | Find indices both peers have. | ||
288 | intersection :: Bitfield -> Bitfield -> Bitfield | ||
289 | intersection a b = {-# SCC intersection #-} Bitfield { | ||
290 | bfSize = bfSize a `min` bfSize b | ||
291 | , bfSet = bfSet a `S.intersection` bfSet b | ||
292 | } | ||
293 | |||
294 | -- | Find indices which have first peer but do not have the second peer. | ||
295 | difference :: Bitfield -> Bitfield -> Bitfield | ||
296 | difference a b = {-# SCC difference #-} Bitfield { | ||
297 | bfSize = bfSize a -- FIXME is it reasonable? | ||
298 | , bfSet = bfSet a `S.difference` bfSet b | ||
299 | } | ||
300 | |||
301 | -- | Find indices the any of the peers have. | ||
302 | unions :: [Bitfield] -> Bitfield | ||
303 | unions = {-# SCC unions #-} foldl' union (haveNone 0) | ||
304 | |||
305 | {----------------------------------------------------------------------- | ||
306 | Serialization | ||
307 | -----------------------------------------------------------------------} | ||
308 | |||
309 | -- | List all /have/ indexes. | ||
310 | toList :: Bitfield -> [PieceIx] | ||
311 | toList Bitfield {..} = S.toList bfSet | ||
312 | |||
313 | -- | Make bitfield from list of /have/ indexes. | ||
314 | fromList :: PieceCount -> [PieceIx] -> Bitfield | ||
315 | fromList s ixs = Bitfield { | ||
316 | bfSize = s | ||
317 | , bfSet = S.splitGT (-1) $ S.splitLT s $ S.fromList ixs | ||
318 | } | ||
319 | |||
320 | -- | Unpack 'Bitfield' from tightly packed bit array. Note resulting | ||
321 | -- size might be more than real bitfield size, use 'adjustSize'. | ||
322 | fromBitmap :: ByteString -> Bitfield | ||
323 | fromBitmap bs = {-# SCC fromBitmap #-} Bitfield { | ||
324 | bfSize = B.length bs * 8 | ||
325 | , bfSet = S.fromByteString bs | ||
326 | } | ||
327 | {-# INLINE fromBitmap #-} | ||
328 | |||
329 | -- | Pack a 'Bitfield' to tightly packed bit array. | ||
330 | toBitmap :: Bitfield -> Lazy.ByteString | ||
331 | toBitmap Bitfield {..} = {-# SCC toBitmap #-} Lazy.fromChunks [intsetBM, alignment] | ||
332 | where | ||
333 | byteSize = bfSize `div` 8 + if bfSize `mod` 8 == 0 then 0 else 1 | ||
334 | alignment = B.replicate (byteSize - B.length intsetBM) 0 | ||
335 | intsetBM = S.toByteString bfSet | ||
336 | |||
337 | {----------------------------------------------------------------------- | ||
338 | -- Piece selection | ||
339 | -----------------------------------------------------------------------} | ||
340 | |||
341 | type Selector = Bitfield -- ^ Indices of client /have/ pieces. | ||
342 | -> Bitfield -- ^ Indices of peer /have/ pieces. | ||
343 | -> [Bitfield] -- ^ Indices of other peers /have/ pieces. | ||
344 | -> Maybe PieceIx -- ^ Zero-based index of piece to request | ||
345 | -- to, if any. | ||
346 | |||
347 | selector :: Selector -- ^ Selector to use at the start. | ||
348 | -> Ratio PieceCount | ||
349 | -> Selector -- ^ Selector to use after the client have | ||
350 | -- the C pieces. | ||
351 | -> Selector -- ^ Selector that changes behaviour based | ||
352 | -- on completeness. | ||
353 | selector start pt ready h a xs = | ||
354 | case strategyClass pt h of | ||
355 | SCBeginning -> start h a xs | ||
356 | SCReady -> ready h a xs | ||
357 | SCEnd -> endGame h a xs | ||
358 | |||
359 | data StartegyClass | ||
360 | = SCBeginning | ||
361 | | SCReady | ||
362 | | SCEnd | ||
363 | deriving (Show, Eq, Ord, Enum, Bounded) | ||
364 | |||
365 | |||
366 | strategyClass :: Ratio PieceCount -> Bitfield -> StartegyClass | ||
367 | strategyClass threshold = classify . completeness | ||
368 | where | ||
369 | classify c | ||
370 | | c < threshold = SCBeginning | ||
371 | | c + 1 % numerator c < 1 = SCReady | ||
372 | -- FIXME numerator have is not total count | ||
373 | | otherwise = SCEnd | ||
374 | |||
375 | |||
376 | -- | Select the first available piece. | ||
377 | strictFirst :: Selector | ||
378 | strictFirst h a _ = Just $ findMin (difference a h) | ||
379 | |||
380 | -- | Select the last available piece. | ||
381 | strictLast :: Selector | ||
382 | strictLast h a _ = Just $ findMax (difference a h) | ||
383 | |||
384 | -- | | ||
385 | rarestFirst :: Selector | ||
386 | rarestFirst h a xs = rarest (map (intersection want) xs) | ||
387 | where | ||
388 | want = difference h a | ||
389 | |||
390 | -- | In average random first is faster than rarest first strategy but | ||
391 | -- only if all pieces are available. | ||
392 | randomFirst :: Selector | ||
393 | randomFirst = do | ||
394 | -- randomIO | ||
395 | error "randomFirst" | ||
396 | |||
397 | endGame :: Selector | ||
398 | endGame = strictLast | ||