1 {-# OPTIONS_GHC -fno-warn-orphans #-}
2 module QuickCheck.Value where
5 import Control.Monad (Monad(..))
6 import Data.Eq (Eq(..))
7 import Data.Function (($), (.))
8 import Data.Functor ((<$>))
9 import Data.Ord (Ord(..))
10 import Prelude (Enum(..), Bounded(..))
12 import Test.Tasty.QuickCheck
13 import qualified Data.List as List
17 import QuickCheck.Merit
18 import QuickCheck.Utils
20 quickcheck :: TestTree
23 [ testGroup "MajorityValue"
24 [ testProperty "compare" $ \(SameLength (x::MajorityValue SchoolGrade,y)) ->
25 expandValue x `compare` expandValue y == x`compare`y
30 (Bounded g, Enum g, Ord g, Arbitrary g) =>
31 Arbitrary (MajorityValue g) where
32 arbitrary = List.head . (majorityValue <$>) <$> arbitraryMerits 1
33 shrink (MajorityValue vs)
35 | otherwise = (MajorityValue <$>) $ List.tail $ List.tails vs
36 instance (Bounded g, Enum g) => Arbitrary (Middle g) where
38 lowG <- choose (fromEnum(minBound::g), fromEnum(maxBound::g))
39 highG <- choose (lowG, fromEnum(maxBound::g))
40 share <- choose (0, 1)
41 return $ Middle share (toEnum lowG) (toEnum highG)
43 (Arbitrary g, Bounded g, Enum g, Ord g) =>
44 Arbitrary (SameLength (MajorityValue g, MajorityValue g)) where
46 SameLength (x,y) <- arbitrary
47 return $ SameLength (MajorityValue x, MajorityValue y)
49 (Arbitrary g, Bounded g, Enum g, Ord g) =>
50 Arbitrary (SameLength ([Middle g], [Middle g])) where
52 SameLength (m0, m1) <- arbitrary
54 ( unMajorityValue $ majorityValue m0
55 , unMajorityValue $ majorityValue m1 )