-----------------------------------------------------------------------------
-- |
-- Module      :  Data.List.Unique
-- Copyright   :  (c) Volodymyr Yaschenko
-- License     :  BSD3
-- 
-- Maintainer  :  ualinuxcn@gmail.com
-- Stability   :  Unstable
-- Portability :  portable
--
-----------------------------------------------------------------------------

module Data.List.Unique 
   (sortUniq 
  , repeated
  , 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 = nub . sort

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 = map head . filterByLength (>1)

-- | 'unique' gets only unique elements, those that do not have duplicates.  
-- It sorts them. Example: 
--
--  unique  "foo bar" == " abfr"
  
unique :: Ord a => [a] -> [a]
unique = concat . filterByLength (==1)

-- | 'count' the elements in the list, 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_' the elements in the list, sorts by values. 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 amount of occurrences of the specified element. Example:  
--
--  countElem 'o' "foo bar" == Just 2

countElem :: Ord a => a -> [a] -> Maybe Int
countElem x = lookup x . count