commit d423031a1ac9fa739fe66dad947fb0e05b5875bf
parent a1de14a79978653fcb1a717c474874d83bba8660
Author: Jared Tobin <jared@jtobin.ca>
Date: Sat, 21 Mar 2015 22:27:25 +1300
Update common soln.
Diffstat:
1 file changed, 10 insertions(+), 11 deletions(-)
diff --git a/20150317_common/Common.hs b/20150317_common/Common.hs
@@ -1,24 +1,24 @@
-{-# LANGUAGE FlexibleInstances #-}
module Common where
+import Control.Monad
import Data.List
import Data.Map (Map)
import qualified Data.Map as Map
-commons :: (Eq a, Ord a) => [[a]] -> [a]
-commons = expand . intersections . fmap toMap
+commons :: Ord a => [[a]] -> [a]
+commons = expand . intersection . fmap sparseRepr
-toMap :: (Eq a, Ord a) => [a] -> Map a Int
-toMap = Map.fromList . fmap labelAndCount . group where
- labelAndCount v = (head $ nub v, length v)
+sparseRepr :: Ord a => [a] -> Map a Int
+sparseRepr = Map.fromList . fmap labelAndCount . group where
+ labelAndCount v = (head (nub v), length v)
-intersections :: (Ord k, Ord v) => [Map k v] -> Map k v
-intersections [] = Map.empty
-intersections (m:ms) = foldl' (Map.intersectionWith min) m ms
+intersection :: (Ord k, Ord v) => [Map k v] -> Map k v
+intersection [] = Map.empty
+intersection (m:ms) = foldl' (Map.intersectionWith min) m ms
expand :: Map a Int -> [a]
-expand = concatMap (uncurry (flip replicate)) . Map.toList
+expand = uncurry (flip replicate) <=< Map.toList
test0 = [1,5,10,20,40,80]
test1 = [6,7,10,20,80,100]
@@ -32,4 +32,3 @@ main :: IO ()
main = do
print $ commons [test0, test1, test2]
print $ commons [test3, test4, test5]
-