summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Network/BitTorrent/Exchange/Block.hs5
-rw-r--r--tests/Network/BitTorrent/Exchange/BlockSpec.hs15
2 files changed, 16 insertions, 4 deletions
diff --git a/src/Network/BitTorrent/Exchange/Block.hs b/src/Network/BitTorrent/Exchange/Block.hs
index 0f437381..6e5b960a 100644
--- a/src/Network/BitTorrent/Exchange/Block.hs
+++ b/src/Network/BitTorrent/Exchange/Block.hs
@@ -317,8 +317,9 @@ spans expectedSize = go 0
317 317
318-- | /O(1)/. A new empty bucket capable to alloof specified size. 318-- | /O(1)/. A new empty bucket capable to alloof specified size.
319empty :: PieceSize -> Bucket 319empty :: PieceSize -> Bucket
320empty 0 = error "empty: Bucket size is zero" 320empty sz
321empty sz = Span sz Nil 321 | sz < 0 = error "empty: Bucket size must be a non-negative value"
322 | otherwise = Span sz Nil
322{-# INLINE empty #-} 323{-# INLINE empty #-}
323 324
324insertSpan :: Pos -> BS.ByteString -> ChunkSize -> Bucket -> Bucket 325insertSpan :: Pos -> BS.ByteString -> ChunkSize -> Bucket -> Bucket
diff --git a/tests/Network/BitTorrent/Exchange/BlockSpec.hs b/tests/Network/BitTorrent/Exchange/BlockSpec.hs
index d0d71906..2dc8e0b8 100644
--- a/tests/Network/BitTorrent/Exchange/BlockSpec.hs
+++ b/tests/Network/BitTorrent/Exchange/BlockSpec.hs
@@ -1,5 +1,6 @@
1module Network.BitTorrent.Exchange.BlockSpec (spec) where 1module Network.BitTorrent.Exchange.BlockSpec (spec) where
2import Control.Applicative 2import Control.Applicative
3import Control.Exception
3import Data.Maybe 4import Data.Maybe
4import Test.Hspec 5import Test.Hspec
5import Test.QuickCheck 6import Test.QuickCheck
@@ -15,10 +16,20 @@ instance Arbitrary BlockIx where
15 arbitrary = BlockIx <$> arbitrary <*> arbitrary <*> arbitrary 16 arbitrary = BlockIx <$> arbitrary <*> arbitrary <*> arbitrary
16 17
17instance Arbitrary Bucket where 18instance Arbitrary Bucket where
18 arbitrary = Block.fromList <$> arbitrary <*> arbitrary 19 arbitrary = do
20 s <- arbitrary `suchThat` (> 0)
21 chunks <- arbitrary
22 return $ Block.fromList s chunks
23
24isSomeException :: SomeException -> Bool
25isSomeException = const True
19 26
20spec :: Spec 27spec :: Spec
21spec = do 28spec = do
22 describe "bucket" $ do 29 describe "empty" $ do
30 it "should fail on bad size" $ do
31 evaluate (Block.empty (-1)) `shouldThrow` isSomeException
32
33 describe "toPiece" $ do
23 it "render to piece when it is full" $ property $ \ bkt -> 34 it "render to piece when it is full" $ property $ \ bkt ->
24 full bkt == isJust (toPiece bkt) \ No newline at end of file 35 full bkt == isJust (toPiece bkt) \ No newline at end of file