[Haskell-beginners] Beginners Digest, Vol 45, Issue 35

Chaddaï Fouché chaddai.fouche at gmail.com
Fri Mar 30 01:11:45 CEST 2012


On Thu, Mar 29, 2012 at 12:19 PM, Lorenzo Bolla <lbolla at gmail.com> wrote:
> Your second solution, a part from non preserving the ordering of the initial
> sequence, also requires the type of the list elements to be an instance of
> Ord.

Sure, but that's an almost inevitable price to get a O(n log n)
algorithm : you must add a constraint, whether Ord or Hashable or
something like that.
Though a solution with Data.Map in two traversal can preserve the
order and still be O(n log n) if the order is important :

> uniqueM :: (Ord a) => [a] -> [a]
> uniqueM xs = filter ((==1).(m M.!)) xs
>   where
>     m = M.fromListWith (+) $ zip xs (repeat 1)

(fromListWith' would be better here but I don't know why, it still
isn't in Data.Map despite it being a very often useful function)

> I've fixed a bug in your first version, where the return values of isIn
> where reversed.

No, no, my version of isIn was correct (according to my logic at
least) : "isIn y xs 0" is always True since x is always at least 0
times in ys, and "isIn y [] n" with n /= 0 is always False since y is
never in [] more than 0 times. The error was in my list comprehension,
of course which should have been : [x | x <- xs, not (isIn x xs 2)]. I
had first written it as a recursive function before I saw that list
comprehension were admitted and rewrote it a bit hastily :)
Maybe isIn should have named isInAtLeast...

>
> module Main where
>
> import Data.List (sort, group)
>
> -- Need ordering on "a"
> uniqueS :: Ord a => [a] -> [a]
> uniqueS = concat . filter (null . drop 1) . group . sort
>
> -- Fixed Chaddai's solution
> -- Only need equivalent relation on "a"
> unique :: Eq a => [a] -> [a]
> unique xs = [x | x <- xs, isIn x xs 2]
>         where isIn :: Eq a => a -> [a] -> Int -> Bool
>               isIn _ _ 0 = False
>               isIn _ [] _ = True
>               isIn y (x:xs) n
>                     | y == x    = isIn y xs (n-1)
>                     | otherwise = isIn y xs n

-- 
Jedaï



More information about the Beginners mailing list