summaryrefslogtreecommitdiff
path: root/tests/Main.hs
blob: ff571b6b2b7d220d324bcfbccab9ef9f3ba06576 (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
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
{-# LANGUAGE OverloadedStrings #-}
module Main (main) where

import Control.Applicative
import qualified Data.ByteString.Lazy as Lazy
import Data.IntervalSet
import Data.List as L
import Data.Ord
import Data.Maybe
import Data.Word
import Data.Text as T
import Network.URI

import Test.Framework (defaultMain)
import Test.Framework.Providers.QuickCheck2 (testProperty)
import Test.QuickCheck

import Data.BEncode
import Data.Bitfield as BF
import Data.Torrent
import Network.BitTorrent as BT

import Debug.Trace
import Encoding


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

instance Arbitrary Text where
  arbitrary = T.pack <$> arbitrary

{-----------------------------------------------------------------------
    Bitfield
-----------------------------------------------------------------------}
-- other properties are tested in IntervalSet

prop_completenessRange :: Bitfield -> Bool
prop_completenessRange bf = 0 <= c && c <= 1
  where
    c = completeness bf

prop_minMax :: Bitfield -> Bool
prop_minMax bf
  | BF.null bf = True
  | otherwise  = BF.findMin bf <= BF.findMax bf

prop_rarestInRange :: [Bitfield] -> Bool
prop_rarestInRange xs = case rarest xs of
  Just r  -> 0 <= r
          && r < totalCount (maximumBy (comparing totalCount) xs)
  Nothing -> True

{- this one should give pretty good coverage -}
prop_differenceDeMorgan :: Bitfield -> Bitfield -> Bitfield -> Bool
prop_differenceDeMorgan a b c =
  (a `BF.difference` (b `BF.intersection` c))
     == ((a `BF.difference` b) `BF.union` (a `BF.difference` c))
  &&
  (a `BF.difference` (b `BF.union` c))
     == ((a `BF.difference` b) `BF.intersection` (a `BF.difference` c))


{-----------------------------------------------------------------------
    Torrent
-----------------------------------------------------------------------}

prop_properBEncode :: Show a => BEncodable a => Eq a => T a -> a -> Bool
prop_properBEncode _ expected = actual == Right expected
  where
    actual = decoded $ Lazy.toStrict $ encoded expected


-- TODO tests for torrent: encoding <-> decoding
instance Arbitrary FileInfo where
  arbitrary = FileInfo <$> arbitrary <*> arbitrary <*> arbitrary

instance Arbitrary ContentInfo where
  arbitrary = oneof
    [ SingleFile <$> arbitrary <*> arbitrary <*> arbitrary
                 <*> arbitrary <*> arbitrary <*> arbitrary
    , MultiFile  <$> arbitrary <*> arbitrary <*> arbitrary
                 <*> arbitrary <*> arbitrary
    ]

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

main :: IO ()
main = defaultMain
  [ testProperty "completeness range"      prop_completenessRange
  , testProperty "rarest in range"         prop_rarestInRange
  , testProperty "min less that max"       prop_minMax
  , testProperty "difference de morgan"    prop_differenceDeMorgan

  , testProperty "file info encoding"      $
      prop_properBEncode (T :: T FileInfo)
  , testProperty "content info encoding"   $
      prop_properBEncode (T :: T ContentInfo)
  , testProperty "torrent encoding" $
      prop_properBEncode (T :: T Torrent)
  ]