{-# LANGUAGE OverloadedLists #-} {-# LANGUAGE TypeFamilies #-} {-# OPTIONS_GHC -fno-warn-orphans #-} module HUnit where import Test.Tasty import Test.Tasty.HUnit import Control.Arrow (second) import Data.Hashable (Hashable) import Data.Ratio ((%)) import Data.Tree (Tree(..)) import GHC.Exts (IsList(..)) import Prelude import qualified Data.HashMap.Strict as HM import Majority.Judgment import Types hunits :: TestTree hunits = testGroup "HUnit" [ testGroup "MajorityValue" $ [ testCompareValue (majorityValue $ Merit [(3,15), (2,7), (1,3), (0::Int,2)]) (majorityValue $ Merit [(3,16), (2,6), (1,2), (0,3)]) , testGroup "Merit" [ let m = mkMerit ['A'..'F'] in testMajorityValueOfMerits [ (The, m [136,307,251,148,84,74]) ] [ (The, [ Middle ( 57 % 1) 'C' 'C' , Middle (137 % 1) 'B' 'C' , Middle (148 % 1) 'B' 'D' , Middle ( 22 % 1) 'B' 'E' , Middle ( 62 % 1) 'A' 'E' , Middle ( 74 % 1) 'A' 'F' ]) ] , let m = mkMerit [ToReject .. TooGood] in testMajorityValueOfMerits [ (This, m [12,10,21,5,5,5,2]) , (That, m [12,16,22,3,3,3,1]) ] [ (This, [ Middle (8 % 1) Acceptable Acceptable , Middle (5 % 1) Insufficient Acceptable , Middle (5 % 1) Insufficient Good , Middle (5 % 1) ToReject VeryGood , Middle (5 % 1) ToReject Perfect , Middle (2 % 1) ToReject TooGood ]) , (That, [ Middle ( 2 % 1) Acceptable Acceptable , Middle (16 % 1) Insufficient Acceptable , Middle ( 2 % 1) ToReject Acceptable , Middle ( 3 % 1) ToReject Good , Middle ( 3 % 1) ToReject VeryGood , Middle ( 3 % 1) ToReject Perfect , Middle ( 1 % 1) ToReject TooGood ]) ] ] , testGroup "MajorityRanking" [ testMajorityValueOfOpinions [ (The, [No,No,No,No,Yes,Yes]) ] [ (The, [ Middle (1 % 1) No No , Middle (2 % 1) No Yes ]) ] , testMajorityValueOfOpinions [ (The, [No,No,No,Yes,Yes,Yes]) ] [ (The, [ Middle (3 % 1) No Yes ]) ] , testMajorityValueOfOpinions [ (The, [No,No,No,No,Yes,Yes,Yes]) ] [ (The, [ Middle (1 % 2) No No , Middle (3 % 1) No Yes ]) ] , testMajorityValueOfOpinions [ (This, [No,No,No,No,Yes,Yes]) , (That, [No,Yes,Yes,Yes,Yes,Yes]) ] [ (This, [ Middle (1 % 1) No No , Middle (2 % 1) No Yes ]) , (That, [ Middle (2 % 1) Yes Yes , Middle (1 % 1) No Yes ]) ] , testMajorityValueOfOpinions [ (This, [No,No,No,No,No,No]) , (That, [No,No,No,Yes,Yes,Yes]) ] [ (This, [Middle (3 % 1) No No]) , (That, [Middle (3 % 1) No Yes]) ] , testMajorityValueOfOpinions [ (This, [Yes,Yes,Yes,Yes,Yes,Yes]) , (That, [No,No,No,Yes,Yes,Yes]) ] [ (This, [Middle (3 % 1) Yes Yes]) , (That, [Middle (3 % 1) No Yes]) ] , testMajorityValueOfOpinions [ (This, [No,No,Yes,Yes,Yes,Yes]) , (That, [No,No,No,Yes,Yes,Yes]) ] [ (This, [ Middle (1 % 1) Yes Yes , Middle (2 % 1) No Yes ]) , (That, [ Middle (3 % 1) No Yes ]) ] , testMajorityValueOfOpinions [ (1::Int, [Perfect,Perfect,VeryGood,Perfect,Perfect,Perfect]) , (2, [Perfect,VeryGood,VeryGood,VeryGood,Good,VeryGood]) , (3, [Acceptable,Perfect,Good,VeryGood,VeryGood,Perfect]) , (4, [VeryGood,Good,Acceptable,Good,Good,Good]) , (5, [Good,Acceptable,VeryGood,Good,Good,Good]) , (6, [VeryGood,Acceptable,Insufficient,Acceptable,Acceptable,Good]) ] [ (1, [ Middle (2 % 1) Perfect Perfect , Middle (1 % 1) VeryGood Perfect ]) , (2, [ Middle (2 % 1) VeryGood VeryGood , Middle (1 % 1) Good Perfect ]) , (3, [ Middle (1 % 1) VeryGood VeryGood , Middle (1 % 1) Good Perfect , Middle (1 % 1) Acceptable Perfect ]) , (4, [ Middle (2 % 1) Good Good , Middle (1 % 1) Acceptable VeryGood ]) , (5, [ Middle (2 % 1) Good Good , Middle (1 % 1) Acceptable VeryGood ]) , (6, [ Middle (1 % 1) Acceptable Acceptable , Middle (1 % 1) Acceptable Good , Middle (1 % 1) Insufficient VeryGood ]) ] ] , testGroup "Section" [ testSection "0 judge" ([]::Choices C2) ([]::Judges Int G6) (node0 []) (Right $ node0 []) , testSection "1 judge, default grade" [This] [(1::Int,ToReject)] (node0 []) (Right $ node0 [(This, [(1,[(ToReject,1%1)])])]) , testSection "1 judge, default grade, 2 choices" [This, That] [(1::Int,ToReject)] (node0 []) (Right $ node0 [ (This, [(1,[(ToReject,1%1)])]) , (That, [(1,[(ToReject,1%1)])]) ]) , testSection "1 judge, default grade" [This] [(1::Int,ToReject)] (node0 [(This,[(1,Section Nothing Nothing)])]) (Right $ node0 [(This,[(1,[(ToReject,1%1)])])]) , testSection "2 judges, default grade" [This] [(1::Int,ToReject), (2::Int,ToReject)] (node0 [ (This, [(1,Section Nothing Nothing)]) ]) (Right $ node0 [ (This, [ (1,[(ToReject,1%1)]) , (2,[(ToReject,1%1)]) ]) ]) , testSection "ErrorSection_unknown_choices" [] [(1::Int,ToReject)] (node0 [(This,[])]) (Left $ ErrorSection_unknown_choices [This]) , testSection "ErrorSection_unknown_choices" [] [(1::Int,ToReject)] (node0 [(This,[(2,Section Nothing Nothing)])]) (Left $ ErrorSection_unknown_choices [This]) , testSection "ErrorSection_unknown_choices" [This] [(1::Int,ToReject)] (node0 [ (This,[(1,Section Nothing Nothing)]) , (That,[(2,Section Nothing Nothing)]) ]) (Left $ ErrorSection_unknown_choices [That]) , testSection "ErrorSection_unknown_judges" [This] [(1::Int,ToReject)] (node0 [(This,[(2,Section Nothing Nothing)])]) (Left $ ErrorSection_unknown_judges [(This,[2])]) , testSection "1 judge, 1 grade" [This] [(1::Int,ToReject)] (node0 [(This,[(1,Section Nothing (Just Acceptable))])]) (Right $ node0 [(This,[(1,[(Acceptable,1%1)])])]) , testSection "1 judge, 1 grade, 2 sections" [This] [(1::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [(This, [(1,Section (Just $ 1%2) Nothing)])] , node0 [(This, [(1,Section (Just $ 1%2) Nothing)])] ]) (Right $ Node [ (This, [(1,[(Acceptable,1%1)])]) ] [ node0 [(This, [(1,[(Acceptable,1%1)])])] , node0 [(This, [(1,[(Acceptable,1%1)])])] ]) , testSection "sectionNodeShare with judge" [This] [(1::Int,ToReject), (2,Insufficient)] (Node [(This, [(1,Section Nothing (Just Acceptable))])] [ node0 $ SectionNode (Just $ 1%3) [(This, [ (1,Section (Just $ 1%2) Nothing) , (2,Section Nothing Nothing) ])] , node0 [(This, [ (1,Section (Just $ 1%2) Nothing) , (2,Section Nothing (Just Good)) ])] ]) (Right $ Node [ (This, [ (1,[(Acceptable,1%2 + 1%2)]) , (2,[(Insufficient,1%3), (Good,2%3)]) ]) ] [ node0 [(This, [ (1,[(Acceptable,1%1)]) , (2,[(Insufficient,1%1)]) ])] , node0 [(This, [ (1,[(Acceptable,1%1)]) , (2,[(Good,1%1)]) ])] ]) , testSection "sectionNodeShare without judge" [This] [(1::Int,ToReject), (2,Insufficient)] (Node [(This, [(1,Section Nothing (Just Acceptable))])] [ node0 $ SectionNode (Just $ 1%3) [(This, [ (1,Section (Just $ 1%2) Nothing) ])] , node0 [(This, [ (1,Section (Just $ 1%2) Nothing) , (2,Section Nothing (Just Good)) ])] ]) (Right $ Node [ (This, [ (1,[(Acceptable,1%2 + 1%2)]) , (2,[(Insufficient,1%3), (Good,2%3)]) ]) ] [ node0 [(This, [ (1,[(Acceptable,1%1)]) , (2,[(Insufficient,1%1)]) ])] , node0 [(This, [ (1,[(Acceptable,1%1)]) , (2,[(Good,1%1)]) ])] ]) , testSection "1 judge, 2 grades, 2 sections" [This] [(1::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [(This, [(1,Section (Just $ 1%2) Nothing)])] , node0 [(This, [(1,Section (Just $ 1%2) (Just Good))])] ]) (Right $ Node [(This, [(1,[(Acceptable,1%2), (Good,1%2)])])] [ node0 [(This, [(1,[(Acceptable,1%1)])])] , node0 [(This, [(1,[(Good,1%1)])])] ]) , testSection "1 judge, 2 grades, 2 sections (1 default)" [This] [(1::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [(This, [(1,Section Nothing Nothing)])] , node0 [(This, [(1,Section (Just $ 1%2) (Just Good))])] ]) (Right $ Node [(This, [(1,[(Acceptable,1%2), (Good,1%2)])])] [ node0 [(This, [(1,[(Acceptable,1%1)])])] , node0 [(This, [(1,[(Good,1%1)])])] ]) , testSection "1 judge, 3 grades, 3 sections (2 default)" [This] [(1::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [(This, [(1,Section Nothing Nothing)])] , node0 [(This, [(1,Section (Just $ 1%2) (Just Good))])] , node0 [(This, [(1,Section Nothing (Just VeryGood))])] ]) (Right $ Node [(This, [(1,[(Acceptable,1%4), (Good,1%2), (VeryGood,1%4)])])] [ node0 [(This, [(1,[(Acceptable,1%1)])])] , node0 [(This, [(1,[(Good,1%1)])])] , node0 [(This, [(1,[(VeryGood,1%1)])])] ]) , testSection "ErrorSection_invalid_shares sum not 1" [This] [(1::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [(This, [(1,Section (Just $ 1%2) Nothing)])] , node0 [(This, [(1,Section (Just $ 1%3) (Just Good))])] ]) (Left $ ErrorSection_invalid_shares [(This, [(1,[1%2,1%3])])]) , testSection "ErrorSection_invalid_shares negative share" [This] [(1::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [(This, [(1,Section (Just $ 1%2) Nothing)])] , node0 [(This, [(1,Section (Just $ -1%2) (Just Good))])] ]) (Left $ ErrorSection_invalid_shares [(This, [(1,[1%2,-1%2])])]) , testSection "2 judges, 3 grade, 3 sections (1 default)" [This] [(1::Int,ToReject), (2::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [ (This, [(1,Section Nothing Nothing)]) ] , node0 [ (This, [(1,Section (Just $ 1%2) (Just Good))]) ] ]) (Right $ Node [ (This, [ (1,[(Acceptable,1%2), (Good,1%2)]) , (2,[(ToReject,1%1)]) ]) ] [ node0 [ (This, [ (1,[(Acceptable,1%1)]) , (2,[(ToReject,1%1)]) ]) ] , node0 [ (This, [ (1,[(Good,1%1)]) , (2,[(ToReject,1%1)]) ]) ] ]) , testSection "2 judges, 4 grades, 5 sections (2 defaults)" [This] [(1::Int,ToReject), (2::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [ (This, [(1,Section Nothing Nothing)]) ] , node0 [ (This, [(1,Section (Just $ 1%2) (Just Good))]) ] , Node [ (This, [(1,Section Nothing (Just Good))]) ] [ node0 [ (This, [ (1,Section Nothing (Just VeryGood)) , (2,Section Nothing (Just Insufficient)) ]) ] ] ]) (Right $ Node [ (This, [ (1,[(Acceptable,1%4), (Good,1%2), (VeryGood,1%4)]) , (2,[(ToReject,2%3), (Insufficient,1%3)]) ]) ] [ node0 [ (This, [ (1,[(Acceptable,1%1)]) , (2,[(ToReject,1%1)]) ]) ] , node0 [ (This, [ (1,[(Good,1%1)]) , (2,[(ToReject,1%1)]) ]) ] , Node [ (This, [ (1,[(VeryGood,1%1)]) , (2,[(Insufficient,1%1)]) ]) ] [ node0 [ (This, [ (1,[(VeryGood,1%1)]) , (2,[(Insufficient,1%1)]) ]) ] ] ]) , testSection "1 judge, default grade, 2 choices" [This, That] [(1::Int,ToReject)] (node0 []) (Right $ node0 [ (This,[(1,[(ToReject,1%1)])]) , (That,[(1,[(ToReject,1%1)])]) ]) , testSection "2 judges, 2 choices" [This, That] [(1::Int,ToReject), (2::Int,ToReject)] (Node [ ] [ node0 [ (This, [(1,Section Nothing (Just Good))]) , (That, [(2,Section Nothing (Just Insufficient))]) ] , node0 [ (This, [(1,Section Nothing (Just Acceptable))]) , (That, [(2,Section Nothing (Just VeryGood))]) ] ]) (Right $ Node [ (This, [ (1,[(Good,1%2), (Acceptable,1%2)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(ToReject,1%1)]) , (2,[(Insufficient,1%2), (VeryGood,1%2)]) ]) ] [ node0 [ (This, [ (1,[(Good,1%1)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(ToReject,1%1)]) , (2,[(Insufficient,1%1)]) ]) ] , node0 [ (This, [ (1,[(Acceptable,1%1)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(ToReject,1%1)]) , (2,[(VeryGood,1%1)]) ]) ] ]) , testSection "1 judge, 1 choice" [This] [(1::Int,ToReject)] (Node [] [ node0 [ (This, [(1,Section (Just $ 1%8) (Just Acceptable))]) ] , node0 [ (This, [(1,Section Nothing Nothing)]) ] ]) (Right $ Node [ (This, [(1,[(Acceptable,1%8), (ToReject,7%8)])]) ] [ node0 [ (This, [(1,[(Acceptable, 1%1)])]) ] , node0 [ (This, [(1,[(ToReject, 1%1)])]) ] ]) , testSection "1 judge, 1 choice (missing judge)" [This] [(1::Int,ToReject)] (Node [] [ node0 [ (This, [(1,Section (Just $ 1%8) (Just Acceptable))]) ] , node0 [ (This, []) ] ]) (Right $ Node [ (This, [(1,[(Acceptable,1%8), (ToReject,7%8)])]) ] [ node0 [ (This, [(1,[(Acceptable, 1%1)])]) ] , node0 [ (This, [(1,[(ToReject, 1%1)])]) ] ]) , testSection "1 judge, 1 choice (missing judge)" [This] [(1::Int,ToReject)] (Node [] [ node0 [ (This, []) ] , node0 [ (This, [(1,Section (Just $ 1%8) (Just Acceptable))]) ] ]) (Right $ Node [ (This, [(1,[(Acceptable,1%8), (ToReject,7%8)])]) ] [ node0 [ (This, [(1,[(ToReject, 1%1)])]) ] , node0 [ (This, [(1,[(Acceptable, 1%1)])]) ] ]) , testSection "1 judge, 1 choice (missing choice)" [This] [(1::Int,ToReject)] (Node [] [ node0 [ (This, [(1,Section (Just $ 1%8) (Just Acceptable))]) ] , node0 [ ] ]) (Right $ Node [ (This, [(1,[(Acceptable,1%8), (ToReject,7%8)])]) ] [ node0 [ (This, [(1,[(Acceptable, 1%1)])]) ] , node0 [ (This, [(1,[(ToReject, 1%1)])]) ] ]) , testSection "1 judge, 1 choice (missing choice)" [This] [(1::Int,ToReject)] (Node [] [ node0 [ ] , node0 [ (This, [(1,Section (Just $ 1%8) (Just Acceptable))]) ] ]) (Right $ Node [ (This, [(1,[(Acceptable,1%8), (ToReject,7%8)])]) ] [ node0 [ (This, [(1,[(ToReject, 1%1)])]) ] , node0 [ (This, [(1,[(Acceptable, 1%1)])]) ] ]) , testSection "2 judges, 2 choices" [This, That] [(1::Int,ToReject), (2::Int,ToReject)] (node0 [ (This, [(1,Section Nothing (Just Acceptable))]) , (That, [(2,Section (Just $ 1%8) (Just VeryGood))]) ]) (Right $ node0 [ (This, [ (1,[(Acceptable,1%1)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(ToReject,1%1)]) , (2,[(VeryGood,1%1)]) ]) ]) , testSection "2 judges, 2 choices" [This, That] [(1::Int,ToReject), (2::Int,ToReject)] (Node [ ] [ node0 [ (This, [(1,Section Nothing (Just Good))]) , (That, [(2,Section Nothing (Just Insufficient))]) ] , node0 [ (This, [(1,Section Nothing (Just Acceptable))]) , (That, [(2,Section (Just $ 1%8) (Just VeryGood))]) ] ]) (Right $ Node [ (This, [ (1,[(Good,1%2), (Acceptable,1%2)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(ToReject,1%1)]) , (2,[(Insufficient,7%8), (VeryGood,1%8)]) ]) ] [ node0 [ (This, [ (1,[(Good,1%1)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(ToReject,1%1)]) , (2,[(Insufficient,1%1)]) ]) ] , node0 [ (This, [ (1,[(Acceptable,1%1)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(ToReject,1%1)]) , (2,[(VeryGood,1%1)]) ]) ] ]) , testSection "2 judges, 2 choices" [This, That] [(1::Int,ToReject), (2::Int,ToReject)] (Node [ (This, [(1,Section Nothing (Just Acceptable))]) ] [ node0 [ (This, [(1,Section Nothing Nothing)]) ] , node0 [ (This, [ (1,Section (Just $ 1%2) (Just Good)) ]) , (That, [ (1,Section (Just $ 1%3) Nothing) , (2,Section (Just $ 1%5) (Just Insufficient)) ]) ] , Node [ (This, [(1,Section Nothing (Just Good))]) , (That, [(2,Section Nothing (Just VeryGood))]) ] [ node0 [ (This, [ (1,Section Nothing (Just VeryGood)) , (2,Section Nothing (Just Insufficient)) ]) , (That, [ (1,Section Nothing (Just Acceptable)) ]) ] , node0 [ (This, [ (1,Section Nothing (Just Acceptable)) ]) , (That, [ (1,Section Nothing (Just VeryGood)) , (2,Section Nothing (Just Good)) ]) ] ] ]) (Right $ Node [ (This, [ (1,[(Acceptable,1%4 + 1%8), (Good,1%2), (VeryGood,1%8)]) , (2,[(ToReject,1%3 + 1%3 + 1%6), (Insufficient,1%6)]) ]) , (That, [ (1,[(ToReject,1%3 + 1%3), (Acceptable,1%6), (VeryGood,1%6)]) , (2,[(ToReject,4%10), (Insufficient,1%5), (VeryGood,4%20), (Good,4%20)]) ]) ] [ node0 [ (This, [ (1,[(Acceptable,1%1)]) -- 1%4 , (2,[(ToReject,1%1)]) -- 1%3 ]) , (That, [ (1,[(ToReject,1%1)]) -- 1%3 , (2,[(ToReject,1%1)]) -- 4%10 ]) ] , node0 [ (This, [ (1,[(Good,1%1)]) -- 1%2 , (2,[(ToReject,1%1)]) -- 1%3 ]) , (That, [ (1,[(ToReject,1%1)]) -- 1%3 , (2,[(Insufficient,1%1)]) -- 1%5 ]) ] , Node [ (This, [ (1,[(VeryGood,1%2), (Acceptable,1%2)]) -- 1%4 , (2,[(Insufficient,1%2), (ToReject,1%2)]) -- 1%3 ]) , (That, [ (1,[(Acceptable,1%2), (VeryGood,1%2)]) -- 1%3 , (2,[(VeryGood,1%2), (Good,1%2)]) -- 4%10 ]) ] [ node0 [ (This, [ (1,[(VeryGood,1%1)]) , (2,[(Insufficient,1%1)]) ]) , (That, [ (1,[(Acceptable,1%1)]) , (2,[(VeryGood,1%1)]) ]) ] , node0 [ (This, [ (1,[(Acceptable,1%1)]) , (2,[(ToReject,1%1)]) ]) , (That, [ (1,[(VeryGood,1%1)]) , (2,[(Good,1%1)]) ]) ] ] ] ) ] ] ] elide :: String -> String elide s | length s > 42 = take 42 s ++ ['…'] | otherwise = s mkMerit :: (Ord grade, Show grade) => [grade] -> [Share] -> Merit grade mkMerit gs = fromList . (gs`zip`) mkMeritByChoice :: (Eq choice, Hashable choice, Ord grade) => [(choice,[grade])] -> MeritByChoice choice grade mkMeritByChoice os = meritByChoice $ fromList $ second (fromList . zip [1::Int ..] . (singleGrade <$>)) <$> os testCompareValue :: (Ord grade, Show grade) => MajorityValue grade -> MajorityValue grade -> TestTree testCompareValue x y = testGroup (elide $ show (unMajorityValue x, unMajorityValue y)) [ testCase "x == x" $ x`compare`x @?= EQ , testCase "y == y" $ y`compare`y @?= EQ , testCase "x < y" $ x`compare`y @?= LT , testCase "y > x" $ y`compare`x @?= GT ] testMajorityRanking :: (Eq choice, Hashable choice, Ord grade, Show grade, Show choice) => [(choice, [grade])] -> MajorityRanking choice grade -> TestTree testMajorityRanking os expect = testCase (elide $ show os) $ majorityRanking (mkMeritByChoice os) @?= expect testMajorityValueOfOpinions :: (Show grade, Show choice, Ord grade, Eq choice, Hashable choice) => [(choice, [grade])] -> [(choice, [Middle grade])] -> TestTree testMajorityValueOfOpinions os expect = testCase (elide $ show os) $ majorityValueByChoice (mkMeritByChoice os) @?= (MajorityValue<$>HM.fromList expect) testMajorityValueOfMerits :: (Show grade, Show choice, Ord grade, Eq choice, Hashable choice) => MeritByChoice choice grade -> [(choice, [Middle grade])] -> TestTree testMajorityValueOfMerits ms expect = testCase (elide $ show $ unMeritByChoice ms) $ majorityValueByChoice ms @?= (MajorityValue<$>HM.fromList expect) testSection :: Eq choice => Hashable choice => Eq judge => Hashable judge => Ord grade => Show choice => Show judge => Show grade => String -> Choices choice -> Judges judge grade -> Tree (SectionNode choice judge grade) -> Either (ErrorSection choice judge grade) (Tree (OpinionsByChoice choice judge grade)) -> TestTree testSection msg cs js ss expect = testCase (elide msg) $ opinionsBySection cs js ss @?= expect node0 :: a -> Tree a node0 = (`Node`[]) instance (Eq choice, Hashable choice) => IsList (SectionNode choice judge grade) where type Item (SectionNode choice judge grade) = (choice, SectionByJudge judge grade) fromList = SectionNode Nothing . fromList toList = GHC.Exts.toList . sectionByJudgeByChoice