Skip to content

Instantly share code, notes, and snippets.

Created June 22, 2017 15:03
Show Gist options
  • Save anonymous/c147082931d7dbebabab862ec33757d9 to your computer and use it in GitHub Desktop.
Save anonymous/c147082931d7dbebabab862ec33757d9 to your computer and use it in GitHub Desktop.
-- L'exercice est de passer le fichier qui se trouve ici
-- https://vote.gnome.org/blt.php?election_id=25
-- et d'en extraire les informations
import Data.List
woBoundaries =
let r = reverse . drop 1
in r . r
clusters_of size list =
map (take size) $ map (`drop` list) [0..length list - size]
compare_lists xs ys
| length xs > length ys = GT
| otherwise = LT
-- compare_size_then_occurences @xs(sx,ox) @xs(sy,ox) =
-- LT
clusters_in range list =
concat
$ concat
$ map (\x -> map (clusters_of x) list) range
love x =
sortBy compare_lists
. map ( \x -> (length x, x !! 0) )
. filter ((> 1) . length)
. group
. filter ((> 1) . length)
. sort
. concat
. map (clusters_of x)
go = do
content <- getContents
let entries = drop 1 $ lines content
let votes =
map (woBoundaries . words)
$ takeWhile (/= "0") entries
let candidates =
map woBoundaries
$ drop 1
$ dropWhile (/= "0") entries
mapM print $ love 4 votes ++ love 5 votes
-- $ clusters_in [4..5] votes
main = go
@bartavelle
Copy link

{-# LANGUAGE TupleSections #-}
module Main where

import Data.List
import Data.List.Split
import qualified Data.Map.Strict as M

clustersOf :: Int -> [a] -> [[a]]
clustersOf s = filter ((== s) . length) . map (take s) . tails

love :: Int -> [[Int]] -> [([Int], Int)]
love size = M.toList
          . M.filter (>1)
          . M.fromListWith (+)
          . map (,1)
          . concatMap (clustersOf size)

main :: IO ()
main = do
  content <- drop 1 . lines <$> getContents
  let (rawvotes, _) = break (=="0") content
      voteValues = init $ splitWhen (== 0) $ concatMap (map read . words) rawvotes
      votes = map (drop 1) voteValues
  mapM_ print (love 4 votes)
  mapM_ print (love 5 votes)

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment