{-# LANGUAGE TypeApplications #-} module QuickCheck.Rank where import Data.Bool import Data.Eq (Eq(..)) import Data.Function (($)) import Data.Functor ((<$>)) import Data.Ratio (numerator) import Prelude (Enum(..), (*), fromIntegral) import Test.Tasty import Test.Tasty.QuickCheck import qualified Data.List as List import Majority.Merit import Majority.Value import Majority.Rank import Types import QuickCheck.Value () quickcheck :: TestTree quickcheck = testGroup "Rank" [ testGroup "majorityValueOfRank . rankOfMajorityValue == id" [ testProperty "SchoolGrade" $ testMVRankMV @SchoolGrade , testProperty "DanishSchoolGrade" $ testMVRankMV @DanishSchoolGrade ] ] testMVRankMV :: forall g. Enum g => MajorityValue g -> Bool testMVRankMV mv = let gs = fromIntegral $ List.length (enumFrom (toEnum 0) :: [g]) in let js = numerator $ (2 *) $ List.sum $ middleShare <$> unMajorityValue mv in majorityValueOfRank js gs (rankOfMajorityValue gs mv') == mv' where ranked a = Ranked (fromIntegral (fromEnum a), ()) mv' = MajorityValue $ (<$> unMajorityValue mv) $ \(Middle s l h) -> Middle s (ranked l) (ranked h)