1 {-# LANGUAGE TypeApplications #-}
2 module QuickCheck.Rank where
5 import Data.Eq (Eq(..))
6 import Data.Function (($))
7 import Data.Functor ((<$>))
8 import Data.Ratio (numerator)
9 import Prelude (Enum(..), (*), fromIntegral)
11 import Test.Tasty.QuickCheck
12 import qualified Data.List as List
18 import QuickCheck.Value ()
20 quickcheck :: TestTree
23 [ testGroup "majorityValueOfRank . rankOfMajorityValue == id"
24 [ testProperty "SchoolGrade" $ testMVRankMV @SchoolGrade
25 , testProperty "DanishSchoolGrade" $ testMVRankMV @DanishSchoolGrade
29 testMVRankMV :: forall g. Enum g => MajorityValue g -> Bool
31 let gs = fromIntegral $ List.length (enumFrom (toEnum 0) :: [g]) in
32 let js = numerator $ (2 *) $ List.sum $ middleShare <$> unMajorityValue mv in
33 majorityValueOfRank js gs (rankOfMajorityValue gs mv') == mv'
35 ranked a = Ranked (fromIntegral (fromEnum a), ())
37 (<$> unMajorityValue mv) $ \(Middle s l h) ->
38 Middle s (ranked l) (ranked h)