module Election( Election, createElection, doCount ) where import qualified System.IO as IO import qualified Control.Monad as Con import qualified Control.Monad.Trans.Either as ET import qualified Control.Monad.IO.Class as MIO import qualified Data.List as List import qualified Data.Either.Unwrap as Either import qualified Counter as Sen import qualified Candidate as Typ import qualified CSV as CSV data Election = Election { getEntries :: [Entry] , getCounter :: Sen.SenateCounter , getLogDir :: FilePath , getTotalPapers :: Int , getQuota :: Int , getNextLogNum :: Int , getVacancies :: Int , isDone :: Bool } data Entry = Entry { getID :: Typ.CandidateID , getVoteChange :: Int , getTotalVotes :: Int , getCritTrace :: [Trace] , getStatus :: Status , getChanged :: Bool } deriving (Eq) data Trace = Trace { getCriteria :: Sen.Criteria , getTransferVal :: Float } deriving (Eq) data Status = Running | Elected | Eliminated deriving (Show, Eq) createElection :: FilePath -> Sen.SenateCounter -> Int -> IO Election createElection outDir counter numToElect = do entries <- mapM (candToEntry counter) (Sen.getBallot counter) let total = Sen.getTotal counter quota = 1 + floor ((fromIntegral total) / (fromIntegral (numToElect + 1))) return (Election entries counter outDir total quota 1 numToElect False) candToEntry :: Sen.SenateCounter -> Typ.CandidateID -> IO Entry candToEntry counter candidate = do let criteria = [(1,candidate)] trace = Trace criteria 1 firstPrefs <- Sen.doCount counter criteria return (Entry candidate firstPrefs firstPrefs [trace] Running False) doCount :: Election -> IO () doCount e = do e' <- writeLog e -- these following calculations probably aren't the -- intended use of Either monads, but the pattern fits -- and it's certainly a lot better than a bunch of -- if-them-else constructs in haskell r <- ET.eitherT return return $ checkDone e' >>= electSomeone >>= checkNoQuota >>= excludeSomeone Con.when (not (isDone r)) $ doCount r checkDone :: Election -> ET.EitherT Election IO Election checkDone e = do let running = filter ((== Running) . getStatus) (getEntries e) if (getVacancies e == 0 || length running == 0) then ET.left (e { isDone = True }) else ET.right e partBeforeAfter :: (Eq a) => a -> [a] -> ([a],[a]) partBeforeAfter item list = let (x,y) = List.break (== item) list in if (length y <= 1) then (x,[]) else (x,tail y) electSomeone :: Election -> ET.EitherT Election IO Election electSomeone e = do let (running, notRunning) = List.partition ((== Running) . getStatus) (getEntries e) electedEntry = List.maximumBy (\x y -> compare (getTotalVotes x) (getTotalVotes y)) running (beforeEntries, afterEntries) = partBeforeAfter electedEntry (getEntries e) newTransferValue = (fromIntegral (getTotalVotes electedEntry - getQuota e)) / (fromIntegral (getTotalVotes electedEntry)) revisedElectedEntry = electedEntry { getStatus = Elected , getChanged = True , getTotalVotes = (getQuota e) , getVoteChange = (getQuota e) - (getTotalVotes electedEntry) } if (getTotalVotes electedEntry >= getQuota e) then do revisedBeforeEntries <- MIO.liftIO $ transferVotes (getCounter e) newTransferValue electedEntry beforeEntries revisedAfterEntries <- MIO.liftIO $ transferVotes (getCounter e) newTransferValue electedEntry afterEntries let revisedEntries = revisedBeforeEntries ++ [revisedElectedEntry] ++ revisedAfterEntries ET.left (e { getEntries = revisedEntries, getVacancies = (getVacancies e) - 1 }) else ET.right e excludeSomeone :: Election -> ET.EitherT Election IO Election excludeSomeone e = do let (running, notRunning) = List.partition ((== Running) . getStatus) (getEntries e) excludedEntry = List.minimumBy (\x y -> compare (getTotalVotes x) (getTotalVotes y)) running (beforeEntries, afterEntries) = partBeforeAfter excludedEntry (getEntries e) revisedExcludedEntry = excludedEntry { getStatus = Eliminated , getChanged = True , getTotalVotes = 0 , getVoteChange = -(getTotalVotes excludedEntry) } if (getTotalVotes excludedEntry < getQuota e) then do revisedBeforeEntries <- MIO.liftIO $ transferVotes (getCounter e) 1 excludedEntry beforeEntries revisedAfterEntries <- MIO.liftIO $ transferVotes (getCounter e) 1 excludedEntry afterEntries let revisedEntries = revisedBeforeEntries ++ [revisedExcludedEntry] ++ revisedAfterEntries ET.left (e { getEntries = revisedEntries }) else ET.right e transferVotes :: Sen.SenateCounter -> Float -> Entry -> [Entry] -> IO [Entry] transferVotes counter value from to = do let addToCriteria candID crit = let maxRank = fst (List.maximumBy (\x y -> compare (fst x) (fst y)) crit) in (maxRank + 1, candID):crit addToTrace candID trace = trace { getCriteria = addToCriteria candID (getCriteria trace) , getTransferVal = value * (getTransferVal trace) } transferFunc entryFrom entryTo = do let newTraces = map (addToTrace (getID entryTo)) (getCritTrace entryFrom) voteList <- Con.mapM (Sen.doCount counter) (map getCriteria newTraces) let changeList = zipWith (*) (map getTransferVal newTraces) (map fromIntegral voteList) totalVoteChange = List.foldl' (+) 0 (map floor changeList) return (entryTo { getVoteChange = totalVoteChange , getTotalVotes = (getTotalVotes entryTo) + totalVoteChange , getCritTrace = newTraces , getChanged = True }) Con.mapM (transferFunc from) to checkNoQuota :: Election -> ET.EitherT Election IO Election checkNoQuota e = do let (running, notRunning) = List.partition ((== Running) . getStatus) (getEntries e) electedEntry = List.maximumBy (\x y -> compare (getTotalVotes x) (getTotalVotes y)) running (beforeEntries, afterEntries) = partBeforeAfter electedEntry (getEntries e) revisedElectedEntry = electedEntry { getStatus = Elected , getChanged = True , getVoteChange = 0 } revisedBeforeEntries = map (\x -> x { getVoteChange = 0, getChanged = False }) beforeEntries revisedAfterEntries = map (\x -> x { getVoteChange = 0, getChanged = False }) afterEntries revisedEntries = revisedBeforeEntries ++ [revisedElectedEntry] ++ revisedAfterEntries if (length running <= getVacancies e + 1) then ET.left (e { getEntries = revisedEntries, getVacancies = getVacancies e - 1 }) else ET.right e writeLog :: Election -> IO Election writeLog e = do let logName = (getLogDir e) ++ "/" ++ (show (getNextLogNum e)) ++ ".csv" header = ["Vacancies", "Total Papers", "Quota", "Candidate", "Votes", "Transfer", "Status", "Changed"] static = [show (getVacancies e), show (getTotalPapers e), show (getQuota e)] dynFunc c = [getID c, show (getTotalVotes c), show (getVoteChange c), show (getStatus c), show (getChanged c)] records = map (\x -> static ++ dynFunc x) (getEntries e) headerLine = CSV.unParseRecord CSV.defaultSettings header recordLines = map (CSV.unParseRecord CSV.defaultSettings) records output = unlines (headerLine:recordLines) IO.writeFile logName output return (e { getNextLogNum = 1 + getNextLogNum e })