summaryrefslogtreecommitdiff
path: root/tests/Data/Torrent/MetainfoSpec.hs
blob: 369c5e0fc268bce2be2c2c121bb71514a9406135 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
{-# LANGUAGE TypeSynonymInstances #-}
{-# OPTIONS -fno-warn-orphans #-}
module Data.Torrent.MetainfoSpec (spec) where

import Control.Applicative
import Data.ByteString as BS
import Data.ByteString.Lazy as BL
import Data.BEncode
import Data.Maybe
import Data.Time
import Network.URI
import Test.Hspec
import Test.QuickCheck
import Test.QuickCheck.Instances ()

import Data.Torrent.Piece
import Data.Torrent.Layout
import Data.Torrent
import Data.Torrent.LayoutSpec ()
import Network.BitTorrent.Core.NodeInfoSpec ()

{-----------------------------------------------------------------------
--  Common
-----------------------------------------------------------------------}

data T a = T

prop_properBEncode :: Show a => BEncode a => Eq a
                   => T a -> a -> IO ()
prop_properBEncode _ expected = actual `shouldBe` Right expected
  where
    actual = decode $ BL.toStrict $ encode expected

instance Arbitrary URI where
  arbitrary = pure $ fromJust
              $ parseURI "http://exsample.com:80/123365_asd"

{-----------------------------------------------------------------------
--  Instances
-----------------------------------------------------------------------}

instance Arbitrary HashList where
  arbitrary = HashList <$> arbitrary

instance Arbitrary PieceInfo where
  arbitrary = PieceInfo <$> arbitrary <*> arbitrary

instance Arbitrary InfoDict where
  arbitrary = infoDictionary <$> arbitrary <*> arbitrary <*> arbitrary

pico :: Gen (Maybe NominalDiffTime)
pico = oneof
  [ pure Nothing
  , (Just . fromIntegral) <$> (arbitrary :: Gen Int)
  ]

instance Arbitrary Torrent where
  arbitrary = Torrent <$> arbitrary
                 <*> arbitrary <*> arbitrary    <*> arbitrary
                 <*> pico      <*> arbitrary    <*> arbitrary
                 <*> arbitrary
                 <*> arbitrary <*> pure Nothing <*> arbitrary

{-----------------------------------------------------------------------
--  Spec
-----------------------------------------------------------------------}

spec :: Spec
spec = do
  describe "FileInfo" $ do
    it "properly bencoded" $ property $
      prop_properBEncode (T :: T (FileInfo BS.ByteString))

  describe "LayoutInfo" $ do
    it "properly bencoded" $ property $
      prop_properBEncode (T :: T LayoutInfo)

  describe "Torrent" $ do
    it "property bencoded" $ property $
      prop_properBEncode (T :: T Torrent)