summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/PeerWire/Bitfield.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/PeerWire/Bitfield.hs')
-rw-r--r--src/Network/BitTorrent/PeerWire/Bitfield.hs62
1 files changed, 58 insertions, 4 deletions
diff --git a/src/Network/BitTorrent/PeerWire/Bitfield.hs b/src/Network/BitTorrent/PeerWire/Bitfield.hs
index 9d88e784..03273899 100644
--- a/src/Network/BitTorrent/PeerWire/Bitfield.hs
+++ b/src/Network/BitTorrent/PeerWire/Bitfield.hs
@@ -22,12 +22,14 @@ module Network.BitTorrent.PeerWire.Bitfield
22 , fromByteString, toByteString 22 , fromByteString, toByteString
23 23
24 -- * Query 24 -- * Query
25 , haveCount, completeness
25 , findMin, findMax 26 , findMin, findMax
26 , union, intersection, difference, combine 27 , union, intersection, difference, combine
27 , frequencies 28 , frequencies
28 29
29 -- * Serialization 30 -- * Serialization
30 , getBitfield, putBitfield, bitfieldByteCount 31 , getBitfield, putBitfield
32 , bitfieldByteCount, bitfieldBitCount
31 33
32 34
33 , aligned, alignLow, alignedZip 35 , aligned, alignLow, alignedZip
@@ -46,9 +48,11 @@ import Data.Word
46 48
47import Foreign 49import Foreign
48 50
49import Network.BitTorrent.PeerWire.Block 51--import Network.BitTorrent.PeerWire.Block
50import Data.Torrent 52import Data.Torrent
51 53
54-- one good idea is to aggregate frequently used stats in reducer
55-- it should give a big boost
52newtype Bitfield = MkBitfield { 56newtype Bitfield = MkBitfield {
53 bfBits :: ByteString 57 bfBits :: ByteString
54-- , bfSize :: Int 58-- , bfSize :: Int
@@ -90,6 +94,11 @@ bitfieldByteCount :: Bitfield -> Int
90bitfieldByteCount = B.length . bfBits 94bitfieldByteCount = B.length . bfBits
91{-# INLINE bitfieldByteCount #-} 95{-# INLINE bitfieldByteCount #-}
92 96
97-- WARN
98-- TODO
99bitfieldBitCount :: Bitfield -> Int
100bitfieldBitCount bf = bitSize (undefined :: Word8) * bitfieldByteCount bf
101{-# INLINE bitfieldBitCount #-}
93 102
94align :: Storable a => Ptr a -> (Ptr a, Int) 103align :: Storable a => Ptr a -> (Ptr a, Int)
95align p = tie (alignPtr p) undefined 104align p = tie (alignPtr p) undefined
@@ -235,7 +244,44 @@ findSet b =
235 else go (succ i) 244 else go (succ i)
236 | otherwise = Nothing 245 | otherwise = Nothing
237 246
247foldBS :: (Word8 -> Int -> Int) -> (Word -> Int -> Int) -> Int -> ByteString -> Int
248foldBS f g acc b =
249 let (fptr, off, len) = B.toForeignPtr b in
250 B.inlinePerformIO $ withForeignPtr fptr $ \_ptr -> do
251 let ptr = _ptr `advancePtr` off
252
253 let (low, mid, hgh) = aligned (ptr, len)
254 let resL = goFold low acc
255 let resM = goFoldW (mid :: Mem Word) resL
256 let resH = goFold hgh resM
257
258 -- computation of res should not escape withForeignPtr
259 case resH of
260 0 -> return ()
261 _ -> return ()
238 262
263 return resH
264
265 where
266 goFold :: Mem Word8 -> Int -> Int
267 goFold (ptr, n) = go 0
268 where
269 go :: Int -> Int -> Int
270 go i !a
271 | i < n =
272 let v = B.inlinePerformIO (peekElemOff ptr i)
273 in go (succ i) (f v a)
274 | otherwise = a
275
276 goFoldW :: Mem Word -> Int -> Int
277 goFoldW (ptr, n) = go 0
278 where
279 go :: Int -> Int -> Int
280 go i !a
281 | i < n =
282 let v = B.inlinePerformIO (peekElemOff ptr i)
283 in go (succ i) (g v a)
284 | otherwise = a
239 285
240union :: Bitfield -> Bitfield -> Bitfield 286union :: Bitfield -> Bitfield -> Bitfield
241union = zipWithBF (.|.) 287union = zipWithBF (.|.)
@@ -257,8 +303,16 @@ combine :: [Bitfield] -> Maybe Bitfield
257combine [] = Nothing 303combine [] = Nothing
258combine as = return $ foldr1 intersection as 304combine as = return $ foldr1 intersection as
259 305
306haveCount :: Bitfield -> Int
307haveCount (MkBitfield b) = foldBS f f 0 b
308 where
309 f byte count = popCount byte + count
310
311completeness :: Bitfield -> (Int, Int)
312completeness bf = (haveCount bf, bitfieldBitCount bf)
313
260-- | Get min index of piece that the peer have. 314-- | Get min index of piece that the peer have.
261findMin :: Bitfield -> Maybe PieceIx 315findMin :: Bitfield -> Maybe Int
262findMin (MkBitfield b) = do 316findMin (MkBitfield b) = do
263 byteIx <- findSet b 317 byteIx <- findSet b
264 bitIx <- findMinWord8 (B.index b byteIx) 318 bitIx <- findMinWord8 (B.index b byteIx)
@@ -271,7 +325,7 @@ findMin (MkBitfield b) = do
271{-# INLINE findMin #-} 325{-# INLINE findMin #-}
272 326
273 327
274findMax :: Bitfield -> Maybe PieceIx 328findMax :: Bitfield -> Maybe Int
275findMax (MkBitfield b) = do 329findMax (MkBitfield b) = do
276 -- TODO avoid reverse 330 -- TODO avoid reverse
277 byteIx <- (pred (B.length b) -) <$> findSet (B.reverse b) 331 byteIx <- (pred (B.length b) -) <$> findSet (B.reverse b)