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

Indeed the second snipper contains quite an obvious mistake. Thanks for noticing!
It doesn't seem to me it utilises a lambda expression though? You mean the '.' operator for chaining function? If that's it, it could be rewritten
unique :: [Integer] -> [Integer]
unique [] = []
unique (x:xs) | elem x xs = unique (filter (/= x) xs)
| otherwise = x : unique xs
----- Original Message -----
From: Ramesh Kumar
Sent: 03/28/12 10:14 AM
To: franco00@gmx.com, beginners@haskell.org
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35
Thanks Franco, Your (first) solution is the only one which has worked so far although it utilizes a lambda expression.
The problem is indeed tricky.
-----------------------------------------------------------------
From: "franco00@gmx.com"

Or, with a one-liner (inefficient, though):
unique xs = [x | x <- xs, length (filter (== x) xs) == 1]
L.
On Wed, Mar 28, 2012 at 9:38 AM,
Indeed the second snipper contains quite an obvious mistake. Thanks for noticing!
It doesn't seem to me it utilises a lambda expression though? You mean the '.' operator for chaining function? If that's it, it could be rewritten
unique :: [Integer] -> [Integer] unique [] = [] unique (x:xs) | elem x xs = unique (filter (/= x) xs)
| otherwise = x : unique xs
----- Original Message -----
From: Ramesh Kumar
Sent: 03/28/12 10:14 AM
To: franco00@gmx.com, beginners@haskell.org
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35
Thanks Franco, Your (first) solution is the only one which has worked so far although it utilizes a lambda expression. The problem is indeed tricky.
------------------------------ *From:* "franco00@gmx.com"
*To:* beginners@haskell.org *Sent:* Wednesday, March 28, 2012 3:39 PM *Subject:* Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35 gah sorry I obviously meant to reply to the "Unique integers in a list" message
----- Original Message ----- From: franco00@gmx.com Sent: 03/28/12 09:36 AM To: beginners@haskell.org Subject: Re: Beginners Digest, Vol 45, Issue 35
unique :: [Integer] -> [Integer] unique [] = [] unique (x:xs) | elem x xs = (unique . filter (/= x)) xs | otherwise = x : unique xs
-- This is a simpler to read version (albeit inefficient?) unique :: [Integer] -> [Integer] unique [] = [] unique (x:xs) | elem x xs = unique xs | otherwise = x : unique xs
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

The evident solution is :
unique xs = [x | x <- xs, isIn x xs 2]
isIn _ _ 0 = True isIn _ [] _ = False isIn y (x:xs) n | y == x = isIn y xs (n-1) | otherwise = isIn y xs n
which is quite obviously O(n^2)... (same idea but just a bit faster than Lorenzo one-liner) The solution proposed here is slightly better : for each element, either he is unique and then it is useless to compare the following elements to it, either he isn't and so none of his subsequent occurrences may be unique, we may proceed with the tail of the list without these occurrences. Note that the second solution of franco00 is wrong because it doesn't remove the subsequent occurrences. Still it is O(n^2) as a sum(k from k=n to k=1). Still, we can get better : O(n log n) with a solution based on a sort or Data.Map :
unique xs = nub (sort xs)
-- Jedaï

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.
I've fixed a bug in your first version, where the return values of isIn
where reversed.
Here they are:
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
main :: IO ()
main = do
print $ uniqueS xs
print $ unique xs
where xs = [1,2,3,3,5,2,1,4]
L.
On Thu, Mar 29, 2012 at 9:30 AM, Chaddaï Fouché
On Thu, Mar 29, 2012 at 10:28 AM, Chaddaï Fouché
wrote: unique xs = nub (sort xs)
oops, I meant :
unique = concat . filter (null . drop 1) . group . sort
-- Jedaï

On Thu, Mar 29, 2012 at 12:19 PM, Lorenzo Bolla
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ï

Folks, Thank you so much for the replies, ideas and comments about my query. 1) However, I'm puzzled, how do you analyze performance when it comes to programs written in a functional language like Haskell. Correct me if I am wrong, functional language programs don't really run like the usual top to bottom flows we have with other (imperative) languages. They're much like Prolog programs, I am tempted to think. 2) Is there any popular paper/tutorial/writeup/book which touches on the performance aspects of Haskell programs? Thank you so much. Ramesh
________________________________ From: Chaddaï Fouché
To: Lorenzo Bolla Cc: beginners@haskell.org Sent: Friday, March 30, 2012 7:11 AM Subject: Re: [Haskell-beginners] Beginners Digest, Vol 45, Issue 35 On Thu, Mar 29, 2012 at 12:19 PM, Lorenzo Bolla
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ï
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (4)
-
Chaddaï Fouché
-
franco00@gmx.com
-
Lorenzo Bolla
-
Ramesh Kumar