diff options
Diffstat (limited to 'src/Network/BitTorrent/PeerWire')
-rw-r--r-- | src/Network/BitTorrent/PeerWire/Bitfield.hs | 12 | ||||
-rw-r--r-- | src/Network/BitTorrent/PeerWire/Selection.hs | 7 |
2 files changed, 13 insertions, 6 deletions
diff --git a/src/Network/BitTorrent/PeerWire/Bitfield.hs b/src/Network/BitTorrent/PeerWire/Bitfield.hs index 2baeb516..9d88e784 100644 --- a/src/Network/BitTorrent/PeerWire/Bitfield.hs +++ b/src/Network/BitTorrent/PeerWire/Bitfield.hs | |||
@@ -18,6 +18,7 @@ module Network.BitTorrent.PeerWire.Bitfield | |||
18 | 18 | ||
19 | -- * Construction | 19 | -- * Construction |
20 | , empty, full | 20 | , empty, full |
21 | , toList | ||
21 | , fromByteString, toByteString | 22 | , fromByteString, toByteString |
22 | 23 | ||
23 | -- * Query | 24 | -- * Query |
@@ -62,6 +63,13 @@ full :: Int -> Bitfield | |||
62 | full n = MkBitfield $ B.replicate (sizeInBase n 8) (complement 0) | 63 | full n = MkBitfield $ B.replicate (sizeInBase n 8) (complement 0) |
63 | {-# INLINE full #-} | 64 | {-# INLINE full #-} |
64 | 65 | ||
66 | toList :: Bitfield -> [Bool] | ||
67 | toList (MkBitfield bs) = concatMap unpkg (B.unpack bs) | ||
68 | where | ||
69 | unpkg :: Word8 -> [Bool] | ||
70 | unpkg byte = L.map (testBit byte) [0..bitSize (undefined :: Word8) - 1] | ||
71 | {-# INLINE toList #-} | ||
72 | |||
65 | fromByteString :: ByteString -> Bitfield | 73 | fromByteString :: ByteString -> Bitfield |
66 | fromByteString = MkBitfield | 74 | fromByteString = MkBitfield |
67 | {-# INLINE fromByteString #-} | 75 | {-# INLINE fromByteString #-} |
@@ -278,5 +286,5 @@ findMax (MkBitfield b) = do | |||
278 | 286 | ||
279 | {-# INLINE findMax #-} | 287 | {-# INLINE findMax #-} |
280 | 288 | ||
281 | frequencies :: [Bitfield] -> UArray PieceIx Int | 289 | frequencies :: [Bitfield] -> [Int] |
282 | frequencies = undefined | 290 | frequencies xs = foldr1 (zipWith (+)) $ map (map fromEnum . toList) xs |
diff --git a/src/Network/BitTorrent/PeerWire/Selection.hs b/src/Network/BitTorrent/PeerWire/Selection.hs index 2e412e06..92285501 100644 --- a/src/Network/BitTorrent/PeerWire/Selection.hs +++ b/src/Network/BitTorrent/PeerWire/Selection.hs | |||
@@ -48,11 +48,10 @@ strictLast h a _ = findMax (difference a h) | |||
48 | 48 | ||
49 | -- | | 49 | -- | |
50 | rarestFirst :: Selector | 50 | rarestFirst :: Selector |
51 | rarestFirst h a xs = error "rarestFirst" | 51 | rarestFirst h a xs = rarest (frequencies (map (intersection want) xs)) |
52 | -- rarest (frequencies (map (intersection want) xs)) | ||
53 | where | 52 | where |
54 | want = difference h a | 53 | want = difference h a |
55 | rarest = undefined | 54 | rarest = Just . head |
56 | 55 | ||
57 | -- | In general random first is faster than rarest first strategy but | 56 | -- | In general random first is faster than rarest first strategy but |
58 | -- only if all pieces are available. | 57 | -- only if all pieces are available. |
@@ -62,7 +61,7 @@ randomFirst = do | |||
62 | error "randomFirst" | 61 | error "randomFirst" |
63 | 62 | ||
64 | endGame :: Selector | 63 | endGame :: Selector |
65 | endGame = undefined | 64 | endGame = strictLast |
66 | 65 | ||
67 | autoSelector :: Selector | 66 | autoSelector :: Selector |
68 | autoSelector = undefined | 67 | autoSelector = undefined |