----------------------------------------------------------------------------- -- | -- Module : Data.List.Unique -- Copyright : (c) Volodymyr Yaschenko -- License : BSD3 -- -- Maintainer : ualinuxcn@gmail.com -- Stability : Unstable -- Portability : portable -- -- Library provides the functions to find unique and duplicate elements in the list module Data.List.Unique (sortUniq , repeated , repeatedBy , unique , count , count_ , countElem ) where import Data.List (sort,group,nub,filter,map,length) import Prelude hiding (map,filter,length) -- | 'sortUniq' sorts the list and removes the duplicates of elements. Example: -- -- sortUniq "foo bar" == " abfor" sortUniq :: Ord a => [a] -> [a] sortUniq = sort . nub filterByLength :: Ord a => (Int -> Bool) -> [a] -> [[a]] filterByLength p = filter (p . length) . group . sort -- | 'repeated' finds only the elements that are present more than once in the list. Example: -- -- repeated "foo bar" == "o" repeated :: Ord a => [a] -> [a] repeated = repeatedBy (>1) -- | The repeatedBy function behaves just like repeated, except it uses a user-supplied equality predicate. -- -- repeatedBy (>2) "This is the test line" == " eist" repeatedBy :: Ord a => (Int -> Bool) -> [a] -> [a] repeatedBy p = map head . filterByLength p -- | 'unique' gets only unique elements, that do not have duplicates. -- It sorts them. Example: -- -- unique "foo bar" == " abfr" unique :: Ord a => [a] -> [a] unique = concat . filterByLength (==1) -- | 'count' of each element in the list, it sorts by keys (elements). Example: -- -- count "foo bar" == [(' ',1),('a',1),('b',1),('f',1),('o',2),('r',1)] count :: Ord a => [a] -> [(a, Int)] count = map (\x -> (head x,length x)) . group . sort -- | 'count_' of each elements in the list, it sorts by their number. Example: -- -- count_ "foo bar" == [(' ',1),('a',1),('b',1),('f',1),('r',1),('o',2)] count_ :: Ord a => [a] -> [(a, Int)] count_ = map (\(x,y) -> (y,x)) . sort . map (\x -> (length x,head x)) . group . sort -- | 'countElem' gets the number of occurrences of the specified element. Example: -- -- countElem 'o' "foo bar" == 2 countElem :: Eq a => a -> [a] -> Int countElem x [] = 0 countElem x (y:ys) = case x == y of False -> countElem x ys True -> 1 + countElem x ys