commit a1de14a79978653fcb1a717c474874d83bba8660
parent f18cf769d0c8696cae95075231e75747428203e7
Author: Jared Tobin <jared@jtobin.ca>
Date: Thu, 19 Mar 2015 22:20:13 +1300
Add common elements exercise.
Diffstat:
2 files changed, 39 insertions(+), 0 deletions(-)
diff --git a/20150310_matches/Matches.hs b/20150310_matches/Matches.hs
@@ -1,6 +1,8 @@
module Matches where
+import Control.Monad
+
appears :: Eq a => [a] -> [a] -> Int
appears = go where
go [] _ = 1
@@ -9,3 +11,5 @@ appears = go where
| b == c = appears bs cs + appears ab cs
| otherwise = appears ab cs
+appears' n = length . filter (== n) . filterM (const [True, False])
+
diff --git a/20150317_common/Common.hs b/20150317_common/Common.hs
@@ -0,0 +1,35 @@
+{-# LANGUAGE FlexibleInstances #-}
+
+module Common where
+
+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
+
+toMap :: (Eq a, Ord a) => [a] -> Map a Int
+toMap = 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
+
+expand :: Map a Int -> [a]
+expand = concatMap (uncurry (flip replicate)) . Map.toList
+
+test0 = [1,5,10,20,40,80]
+test1 = [6,7,10,20,80,100]
+test2 = [3,4,15,20,30,70,80,120]
+
+test3 = [1,5,5,5]
+test4 = [3,4,5,5,10]
+test5 = [5,5,10,20]
+
+main :: IO ()
+main = do
+ print $ commons [test0, test1, test2]
+ print $ commons [test3, test4, test5]
+