summaryrefslogtreecommitdiff
path: root/tests/Data/Torrent
diff options
context:
space:
mode:
Diffstat (limited to 'tests/Data/Torrent')
-rw-r--r--tests/Data/Torrent/InfoHashSpec.hs38
-rw-r--r--tests/Data/Torrent/LayoutSpec.hs30
-rw-r--r--tests/Data/Torrent/MagnetSpec.hs44
-rw-r--r--tests/Data/Torrent/MetainfoSpec.hs78
-rw-r--r--tests/Data/Torrent/PieceSpec.hs13
5 files changed, 0 insertions, 203 deletions
diff --git a/tests/Data/Torrent/InfoHashSpec.hs b/tests/Data/Torrent/InfoHashSpec.hs
deleted file mode 100644
index 9accc741..00000000
--- a/tests/Data/Torrent/InfoHashSpec.hs
+++ /dev/null
@@ -1,38 +0,0 @@
1{-# OPTIONS -fno-warn-orphans #-}
2module Data.Torrent.InfoHashSpec (spec) where
3
4import Control.Applicative
5import Data.ByteString as BS
6import Data.Convertible
7import System.FilePath
8import Test.Hspec
9import Test.QuickCheck
10import Test.QuickCheck.Instances ()
11
12import Data.Torrent
13
14instance Arbitrary InfoHash where
15 arbitrary = do
16 bs <- BS.pack <$> vectorOf 20 arbitrary
17 pure $ either (const (error "arbitrary infohash")) id $ safeConvert bs
18
19type TestPair = (FilePath, String)
20
21-- TODO add a few more torrents here
22torrentList :: [TestPair]
23torrentList =
24 [ ( "res" </> "dapper-dvd-amd64.iso.torrent"
25 , "0221caf96aa3cb94f0f58d458e78b0fc344ad8bf")
26 ]
27
28infohashSpec :: (FilePath, String) -> Spec
29infohashSpec (filepath, expectedHash) = do
30 it ("should match " ++ filepath) $ do
31 torrent <- fromFile filepath
32 let actualHash = show $ idInfoHash $ tInfoDict torrent
33 actualHash `shouldBe` expectedHash
34
35spec :: Spec
36spec = do
37 describe "info hash" $ do
38 mapM_ infohashSpec torrentList
diff --git a/tests/Data/Torrent/LayoutSpec.hs b/tests/Data/Torrent/LayoutSpec.hs
deleted file mode 100644
index a3fe7c02..00000000
--- a/tests/Data/Torrent/LayoutSpec.hs
+++ /dev/null
@@ -1,30 +0,0 @@
1{-# LANGUAGE GeneralizedNewtypeDeriving #-}
2{-# LANGUAGE StandaloneDeriving #-}
3module Data.Torrent.LayoutSpec (spec) where
4
5import Control.Applicative
6import Test.Hspec
7import Test.QuickCheck
8import System.Posix.Types
9
10import Data.Torrent
11
12
13instance Arbitrary COff where
14 arbitrary = fromIntegral <$> (arbitrary :: Gen Int)
15
16instance Arbitrary a => Arbitrary (FileInfo a) where
17 arbitrary = FileInfo <$> arbitrary <*> arbitrary <*> arbitrary
18
19instance Arbitrary LayoutInfo where
20 arbitrary = oneof
21 [ SingleFile <$> arbitrary
22 , MultiFile <$> arbitrary <*> arbitrary
23 ]
24
25spec :: Spec
26spec = do
27 describe "accumPosition" $ do
28 it "" $ property $ \ p1 p2 p3 s1 s2 s3 ->
29 accumPositions [(p1, s1), (p2, s2), (p3, s3)]
30 `shouldBe` [(p1, (0, s1)), (p2, (s1, s2)), (p3, (s1 + s2, s3))] \ No newline at end of file
diff --git a/tests/Data/Torrent/MagnetSpec.hs b/tests/Data/Torrent/MagnetSpec.hs
deleted file mode 100644
index 838df570..00000000
--- a/tests/Data/Torrent/MagnetSpec.hs
+++ /dev/null
@@ -1,44 +0,0 @@
1{-# OPTIONS -fno-warn-orphans #-}
2module Data.Torrent.MagnetSpec (spec) where
3
4import Control.Applicative
5import Data.Maybe
6import Data.Monoid
7import Test.Hspec
8import Test.QuickCheck
9import Test.QuickCheck.Instances ()
10import Network.URI
11
12import Data.Torrent
13import Data.Torrent.InfoHashSpec ()
14
15
16instance Arbitrary URIAuth where
17 arbitrary = URIAuth <$> arbitrary <*> arbitrary <*> arbitrary
18
19instance Arbitrary URI where
20 arbitrary
21 = pure $ fromJust $ parseURI "http://ietf.org/1737.txt?a=1&b=h#123"
22
23instance Arbitrary Magnet where
24 arbitrary = Magnet <$> arbitrary <*> arbitrary
25 <*> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
26 <*> arbitrary <*> arbitrary <*> pure mempty
27
28magnetEncoding :: Magnet -> IO ()
29magnetEncoding m = parseMagnet (renderMagnet m) `shouldBe` Just m
30
31spec :: Spec
32spec = do
33 describe "Magnet" $ do
34 it "properly encoded" $ property $ magnetEncoding
35
36 it "parse base32" $ do
37 let magnet = "magnet:?xt=urn:btih:CT76LXJDDCH5LS2TUHKH6EUJ3NYKX4Y6"
38 let ih = "CT76LXJDDCH5LS2TUHKH6EUJ3NYKX4Y6"
39 parseMagnet magnet `shouldBe` Just (nullMagnet ih)
40
41 it "parse base16" $ do
42 let magnet = "magnet:?xt=urn:btih:0123456789abcdef0123456789abcdef01234567"
43 let ih = "0123456789abcdef0123456789abcdef01234567"
44 parseMagnet magnet `shouldBe` Just (nullMagnet ih)
diff --git a/tests/Data/Torrent/MetainfoSpec.hs b/tests/Data/Torrent/MetainfoSpec.hs
deleted file mode 100644
index 1a8f97c7..00000000
--- a/tests/Data/Torrent/MetainfoSpec.hs
+++ /dev/null
@@ -1,78 +0,0 @@
1{-# LANGUAGE TypeSynonymInstances #-}
2{-# OPTIONS -fno-warn-orphans #-}
3module Data.Torrent.MetainfoSpec (spec) where
4
5import Control.Applicative
6import Data.ByteString as BS
7import Data.ByteString.Lazy as BL
8import Data.BEncode
9import Data.Maybe
10import Data.Time
11import Network.URI
12import Test.Hspec
13import Test.QuickCheck
14import Test.QuickCheck.Instances ()
15
16import Data.Torrent
17import Data.Torrent.LayoutSpec ()
18import Network.BitTorrent.Core.NodeInfoSpec ()
19
20{-----------------------------------------------------------------------
21-- Common
22-----------------------------------------------------------------------}
23
24data T a = T
25
26prop_properBEncode :: Show a => BEncode a => Eq a
27 => T a -> a -> IO ()
28prop_properBEncode _ expected = actual `shouldBe` Right expected
29 where
30 actual = decode $ BL.toStrict $ encode expected
31
32instance Arbitrary URI where
33 arbitrary = pure $ fromJust
34 $ parseURI "http://exsample.com:80/123365_asd"
35
36{-----------------------------------------------------------------------
37-- Instances
38-----------------------------------------------------------------------}
39
40instance Arbitrary HashList where
41 arbitrary = HashList <$> arbitrary
42
43instance Arbitrary PieceInfo where
44 arbitrary = PieceInfo <$> arbitrary <*> arbitrary
45
46instance Arbitrary InfoDict where
47 arbitrary = infoDictionary <$> arbitrary <*> arbitrary <*> arbitrary
48
49pico :: Gen (Maybe NominalDiffTime)
50pico = oneof
51 [ pure Nothing
52 , (Just . fromIntegral) <$> (arbitrary :: Gen Int)
53 ]
54
55instance Arbitrary Torrent where
56 arbitrary = Torrent <$> arbitrary
57 <*> arbitrary <*> arbitrary <*> arbitrary
58 <*> pico <*> arbitrary <*> arbitrary
59 <*> arbitrary
60 <*> arbitrary <*> pure Nothing <*> arbitrary
61
62{-----------------------------------------------------------------------
63-- Spec
64-----------------------------------------------------------------------}
65
66spec :: Spec
67spec = do
68 describe "FileInfo" $ do
69 it "properly bencoded" $ property $
70 prop_properBEncode (T :: T (FileInfo BS.ByteString))
71
72 describe "LayoutInfo" $ do
73 it "properly bencoded" $ property $
74 prop_properBEncode (T :: T LayoutInfo)
75
76 describe "Torrent" $ do
77 it "property bencoded" $ property $
78 prop_properBEncode (T :: T Torrent)
diff --git a/tests/Data/Torrent/PieceSpec.hs b/tests/Data/Torrent/PieceSpec.hs
deleted file mode 100644
index d3933396..00000000
--- a/tests/Data/Torrent/PieceSpec.hs
+++ /dev/null
@@ -1,13 +0,0 @@
1{-# OPTIONS_GHC -fno-warn-orphans #-}
2module Data.Torrent.PieceSpec (spec) where
3import Control.Applicative
4import Test.Hspec
5import Test.QuickCheck
6import Data.Torrent
7
8
9instance Arbitrary a => Arbitrary (Piece a) where
10 arbitrary = Piece <$> arbitrary <*> arbitrary
11
12spec :: Spec
13spec = return () \ No newline at end of file