module Data.Voting.BordaCount (
Vote(..)
, Ballot(..)
, BallotError(..)
, ballot
, Result(..)
, Score(..)
, Zeros(..)
, ElectionError(..)
, election
, election'
, findFirstDuplicateBy
) where
import Data.Function (on)
import Data.List (find, foldl', nubBy)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
data Vote o = Vote {
voteRanking :: Int
, voteOption :: o
} deriving (Eq, Show)
data Ballot p o = Ballot {
ballotParticipant :: p
, ballotVotes :: [Vote o]
} deriving (Eq, Show)
ballot :: Eq o => p -> [Vote o] -> Either (BallotError o) (Ballot p o)
ballot p votes = do
() <- checkDoubleVotes
() <- checkNonZeros
return $ Ballot p votes
where
zeros = filter ((== 0) . voteRanking) votes
nonZeros = filter ((/= 0) . voteRanking) votes
checkNonZeros =
case findFirstDuplicateBy ((==) `on` voteRanking) nonZeros of
Just (v, v') -> Left $ DuplicateRanking (voteOption v) (voteOption v')
Nothing -> Right ()
checkDoubleVotes =
case findFirstDuplicateBy ((==) `on` voteOption) votes of
Just (v, _) -> Left $ DuplicateOption (voteOption v)
Nothing -> Right ()
data Result o = Result o Score Zeros deriving (Eq, Show)
newtype Score = Score Double deriving (Eq, Num, Ord, Real, Show)
newtype Zeros = Zeros Double deriving (Eq, Num, Ord, Real, Show)
election :: (Eq p, Ord o)
=> (p -> Double)
-> [Ballot p o]
-> Either (ElectionError p) [Result o]
election weigh ballots = do
() <- checkUniqueParticipants
return . M.elems $ foldl' process M.empty ballots
where
checkUniqueParticipants =
case findFirstDuplicateBy ((==) `on` ballotParticipant) ballots of
Just (b, _) -> Left $ DuplicateParticipant (ballotParticipant b)
Nothing -> Right ()
process m b =
let w = weigh (ballotParticipant b) in
foldl' (register w) m (ballotVotes b)
register w m v
| 0 <- voteRanking v
= M.insertWith plus (voteOption v) (Result (voteOption v) 0 (Zeros w)) m
| n <- voteRanking v
, s <- fromIntegral n * w
= M.insertWith plus (voteOption v) (Result (voteOption v) (Score s) 0) m
plus (Result o s z) (Result _ s' z') = Result o (s + s') (z + z')
election' :: (Eq p, Ord o)
=> [Ballot p o]
-> Either (ElectionError p) [Result o]
election' = election (const 1.0)
findFirstDuplicateBy :: (a -> a -> Bool) -> [a] -> Maybe (a, a)
findFirstDuplicateBy _ [] = Nothing
findFirstDuplicateBy f (x:xs) = case find (f x) xs of
Just x' -> Just (x, x')
Nothing -> findFirstDuplicateBy f xs
data BallotError o = DuplicateRanking o o
| DuplicateOption o
deriving (Eq, Show)
newtype ElectionError p = DuplicateParticipant p
deriving (Eq, Show)