removing duplicate tuples (including symmetrical ones)

Hi all, I apologize for spamming this forum so frequently, but there is noone I can turn to around here... I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples. I implemented it using the template from delete from Prelude. Seems like my typse signature has some troubles (Paarse error in pattern) but I am not sure where the problem is. removeDuplTuples :: [(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b] -- using the syntactic sugar for single element in list removeDuplTuples x:xs = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs) I assume the problem lies in elem (snd x,fst x) xs but I am not sure how to rewrite it. Thanks for all help, Martin

Hi Martin,
You have some typos:
import Data.List
removeDuplTuples :: (Eq a) => [(a,a)] -> [(a,a)]
removeDuplTuples [] = []
removeDuplTuples [b] =
[b]
-- using the syntactic sugar for single element in list
removeDuplTuples (x:xs) = nub (if elem (snd x,fst x) xs then
removeDuplTuples xs else [x] ++ removeDuplTuples xs)
--------
You forgot the parenthesis. Parse error in pattern usually means a type in
the input of one of your functions. Nub needs elements that can be equal.
Nub is quitte inefficient, if your elements can be ordered, there is a more
efficient version. It is something like:
fmap head.group.sort $ [1,1,1,1,4,4,5,6,6,7,8,9]
[1,4,5,6,7,8,9]
But I haven't test it thoroughly.
Greets,
Edgar
On Tue, Sep 28, 2010 at 11:33 AM, Martin Tomko
Hi all, I apologize for spamming this forum so frequently, but there is noone I can turn to around here... I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples. I implemented it using the template from delete from Prelude. Seems like my typse signature has some troubles (Paarse error in pattern) but I am not sure where the problem is.
removeDuplTuples :: [(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b]
-- using the syntactic sugar for single element in list removeDuplTuples x:xs = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs)
I assume the problem lies in elem (snd x,fst x) xs but I am not sure how to rewrite it.
Thanks for all help, Martin _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

You forgot the parenthesis. Parse error in pattern usually means a type in the input of one of your functions. Nub needs >elements that can be equal.
type has to be typo.
On Tue, Sep 28, 2010 at 11:44 AM, edgar klerks
Hi Martin,
You have some typos:
import Data.List removeDuplTuples :: (Eq a) => [(a,a)] -> [(a,a)]
removeDuplTuples [] = [] removeDuplTuples [b] = [b] -- using the syntactic sugar for single element in list removeDuplTuples (x:xs) = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs) -------- You forgot the parenthesis. Parse error in pattern usually means a type in the input of one of your functions. Nub needs elements that can be equal.
Nub is quitte inefficient, if your elements can be ordered, there is a more efficient version. It is something like:
fmap head.group.sort $ [1,1,1,1,4,4,5,6,6,7,8,9] [1,4,5,6,7,8,9]
But I haven't test it thoroughly.
Greets,
Edgar
On Tue, Sep 28, 2010 at 11:33 AM, Martin Tomko
wrote: Hi all, I apologize for spamming this forum so frequently, but there is noone I can turn to around here... I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples. I implemented it using the template from delete from Prelude. Seems like my typse signature has some troubles (Paarse error in pattern) but I am not sure where the problem is.
removeDuplTuples :: [(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b]
-- using the syntactic sugar for single element in list removeDuplTuples x:xs = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs)
I assume the problem lies in elem (snd x,fst x) xs but I am not sure how to rewrite it.
Thanks for all help, Martin _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Edgar, thanks for the help. I wanted to first test with nub, but I still cannot get it to work. I cannot see any missing parenthesis, but I retyped it this way to check: removeDuplTuples :: (Eq a) =>[(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b] removeDuplTuples x:xs = nub(if ((snd x,fst x) `elem` xs) then (removeDuplTuples xs) else ([x] ++ removeDuplTuples xs)) still the same error What am I missing? Martin On 9/28/2010 11:45 AM, edgar klerks wrote:
You forgot the parenthesis. Parse error in pattern usually means a type in the input of one of your functions. Nub needs >elements that can be equal.
type has to be typo. On Tue, Sep 28, 2010 at 11:44 AM, edgar klerks
mailto:edgar.klerks@gmail.com> wrote: Hi Martin,
You have some typos:
import Data.List removeDuplTuples :: (Eq a) => [(a,a)] -> [(a,a)]
removeDuplTuples [] = [] removeDuplTuples [b] = [b] -- using the syntactic sugar for single element in list removeDuplTuples (x:xs) = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs) -------- You forgot the parenthesis. Parse error in pattern usually means a type in the input of one of your functions. Nub needs elements that can be equal.
Nub is quitte inefficient, if your elements can be ordered, there is a more efficient version. It is something like:
fmap head.group.sort $ [1,1,1,1,4,4,5,6,6,7,8,9] [1,4,5,6,7,8,9]
But I haven't test it thoroughly.
Greets,
Edgar
On Tue, Sep 28, 2010 at 11:33 AM, Martin Tomko
mailto:martin.tomko@geo.uzh.ch> wrote: Hi all, I apologize for spamming this forum so frequently, but there is noone I can turn to around here... I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples. I implemented it using the template from delete from Prelude. Seems like my typse signature has some troubles (Paarse error in pattern) but I am not sure where the problem is.
removeDuplTuples :: [(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b]
-- using the syntactic sugar for single element in list removeDuplTuples x:xs = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs)
I assume the problem lies in elem (snd x,fst x) xs but I am not sure how to rewrite it.
Thanks for all help, Martin _______________________________________________ Beginners mailing list Beginners@haskell.org mailto:Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

You made the same mistake :)
removeDuplTuples x:xs = nub(if ((snd x,fst x) `elem` xs) then
(removeDuplTuples xs) else ([x] ++ removeDuplTuples xs))
Should be:
removeDuplTuples (x:xs) = nub(if ((snd x,fst x) `elem` xs) then
(removeDuplTuples xs) else ([x] ++ removeDuplTuples xs))
You need to put parenthesis around x:xs.
Greets,
Edgar
On Tue, Sep 28, 2010 at 11:57 AM, Martin Tomko
Hi Edgar, thanks for the help. I wanted to first test with nub, but I still cannot get it to work. I cannot see any missing parenthesis, but I retyped it this way to check:
removeDuplTuples :: (Eq a) =>[(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b] removeDuplTuples x:xs = nub(if ((snd x,fst x) `elem` xs) then (removeDuplTuples xs) else ([x] ++ removeDuplTuples xs))
still the same error
What am I missing? Martin
On 9/28/2010 11:45 AM, edgar klerks wrote:
You forgot the parenthesis. Parse error in pattern usually means a type in the input of one of your functions. Nub needs >elements that can be equal.
type has to be typo. On Tue, Sep 28, 2010 at 11:44 AM, edgar klerks
wrote: Hi Martin,
You have some typos:
import Data.List removeDuplTuples :: (Eq a) => [(a,a)] -> [(a,a)]
removeDuplTuples [] = [] removeDuplTuples [b] = [b] -- using the syntactic sugar for single element in list removeDuplTuples (x:xs) = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs) -------- You forgot the parenthesis. Parse error in pattern usually means a type in the input of one of your functions. Nub needs elements that can be equal.
Nub is quitte inefficient, if your elements can be ordered, there is a more efficient version. It is something like:
fmap head.group.sort $ [1,1,1,1,4,4,5,6,6,7,8,9] [1,4,5,6,7,8,9]
But I haven't test it thoroughly.
Greets,
Edgar
On Tue, Sep 28, 2010 at 11:33 AM, Martin Tomko
wrote: Hi all, I apologize for spamming this forum so frequently, but there is noone I can turn to around here... I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples. I implemented it using the template from delete from Prelude. Seems like my typse signature has some troubles (Paarse error in pattern) but I am not sure where the problem is.
removeDuplTuples :: [(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b]
-- using the syntactic sugar for single element in list removeDuplTuples x:xs = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs)
I assume the problem lies in elem (snd x,fst x) xs but I am not sure how to rewrite it.
Thanks for all help, Martin _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Tuesday 28 September 2010 11:44:41, edgar klerks wrote:
Hi Martin,
You have some typos:
import Data.List removeDuplTuples :: (Eq a) => [(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b] -- using the syntactic sugar for single element in list removeDuplTuples (x:xs) = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs) -------- You forgot the parenthesis. Parse error in pattern usually means a type in the input of one of your functions. Nub needs elements that can be equal.
Nub is quitte inefficient,
Yes, it's O(n^2), but at its type (requiring only equality,no ordering), no more efficient solution is known [perhaps it can even be proved that O(n^2) is the best you can achieve]. If you have an Ord instance, it can be done in O(n*log n), so if you can assume that, it's better to not use nub.
if your elements can be ordered, there is a more efficient version. It is something like:
fmap head.group.sort $ [1,1,1,1,4,4,5,6,6,7,8,9] [1,4,5,6,7,8,9]
Yes, that's a typical idiom. It doesn't quite solve the problem at hand, because Martin also wants to remove one of [(1,2),(2,1)]. If no Ord instance is available, symEq :: Eq a => (a,a) -> (a,a) -> Bool symEq (x,y) (u,v) = (x == u && y == v) || (x == v && y == u) -- parentheses not necessary removeDuplTuples :: Eq a => [(a,a)] -> [(a,a)] removeDuplTuples = nubBy symEq If Ord is available, you can for example write a comparison function symComp and use removeDuplTuples :: Ord a => [(a,a)] -> [(a,a)] removeDuplTuples = map head . groupBy symEq . sortBy symComp Or you map the tuples to a normalized representation first normalize t@(x,y) | y < x = (y,x) | otherwise = t and have removeDuplTuples = map head . group . sort . map normalize or you can decorate-sort-undecorate, or ...
But I haven't test it thoroughly.
Greets,
Edgar
On Tue, Sep 28, 2010 at 11:33 AM, Martin Tomko
Hi all, I apologize for spamming this forum so frequently, but there is noone I can turn to around here... I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples. I implemented it using the template from delete from Prelude. Seems like my typse signature has some troubles (Paarse error in pattern) but I am not sure where the problem is.
removeDuplTuples :: [(a,a)] -> [(a,a)] removeDuplTuples [] = [] removeDuplTuples [b] = [b]
-- using the syntactic sugar for single element in list removeDuplTuples x:xs = nub (if elem (snd x,fst x) xs then removeDuplTuples xs else [x] ++ removeDuplTuples xs)
I assume the problem lies in elem (snd x,fst x) xs but I am not sure how to rewrite it.
Thanks for all help, Martin

Hi,
On 28 September 2010 10:33, Martin Tomko
I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples.
You can of course do this. One approach would be to simply 'fix' the tuples according to some ordering, and then use standard nub - or a better one. But to me, the real question is this: If the order of your tuples to don't matter, do you actually need tuples? There are other types in which the order of the elements in a container does not change the meaning; such as a set. You may want to use a Set from Data.Set, or you can define a pair type in which ordering doesn't matter. It will end up being a cardinality restricted set type though. If you just want to get it working, here is some code for the first option: nubSym :: Ord a => [(a,a)] -> [(a,a)] nubSym = nub . map fix where fix (a,b) | a > b = (b,a) fix p = p Cheers, Ozgur

Hi Ozgur, well, I am getting a list of tuples from a previous function, and they relate to edges in graphs, so I am not too keen to change that, although that could be possible. But I never worked with sets in Haskell, so will have to study. Regarding your suggestion - I have to study it, it is a bit advanced. First, I see there is no paramter to nubSym - I have never used that syntax, shouldn't there be something like nymSym (x:xs) or so? Second, obviously there is a local function, fix. I understand this: fix (a,b) | a > b = (b,a) but I am not sure how to interpret this: fix p = p. Where does p come from? How does haskell know that it relates to (a,b), or the x as parameter? Just asking for clarification ,as I am new to all this. Thanks M. On 9/28/2010 12:05 PM, Ozgur Akgun wrote:
Hi,
On 28 September 2010 10:33, Martin Tomko
mailto:martin.tomko@geo.uzh.ch> wrote: I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples.
You can of course do this. One approach would be to simply 'fix' the tuples according to some ordering, and then use standard nub - or a better one.
But to me, the real question is this: If the order of your tuples to don't matter, do you actually need tuples? There are other types in which the order of the elements in a container does not change the meaning; such as a set. You may want to use a Set from Data.Set, or you can define a pair type in which ordering doesn't matter. It will end up being a cardinality restricted set type though.
If you just want to get it working, here is some code for the first option:
nubSym :: Ord a => [(a,a)] -> [(a,a)] nubSym = nub . map fix where fix (a,b) | a > b = (b,a) fix p = p
Cheers, Ozgur

I'll first try to give you a more understandable syntax. (I hope.)
nubSym :: Ord a => [(a,a)] -> [(a,a)]
nubSym xs = nub (map fix xs)
where fix (a,b) | a > b = (b,a)
| otherwise = (a,b)
The two changes above are getting rid of the point-free style[1] and trading
the pattern matching syntax for guards[2].
In the first version the p was for matching with any parameter that didn't
match the first definition. You may want to have a look at how pattern
matching in Haskell works. (Well, you can find lots of resources about this
one but I would have a look at [3])
[1] http://www.haskell.org/haskellwiki/Pointfree
[2] http://en.wikibooks.org/wiki/Haskell/Control_structures#Guards
[3] http://learnyouahaskell.com/syntax-in-functions
happy hacking! :)
On 28 September 2010 11:14, Martin Tomko
Hi Ozgur, well, I am getting a list of tuples from a previous function, and they relate to edges in graphs, so I am not too keen to change that, although that could be possible. But I never worked with sets in Haskell, so will have to study.
Regarding your suggestion - I have to study it, it is a bit advanced. First, I see there is no paramter to nubSym - I have never used that syntax, shouldn't there be something like nymSym (x:xs) or so? Second, obviously there is a local function, fix. I understand this: fix (a,b) | a > b = (b,a) but I am not sure how to interpret this: fix p = p. Where does p come from? How does haskell know that it relates to (a,b), or the x as parameter?
Just asking for clarification ,as I am new to all this.
Thanks M.
On 9/28/2010 12:05 PM, Ozgur Akgun wrote:
Hi,
On 28 September 2010 10:33, Martin Tomko
wrote: I have a list of (a,a) tuples, and am trying something like nub, but also matching for symmetrical tuples.
You can of course do this. One approach would be to simply 'fix' the tuples according to some ordering, and then use standard nub - or a better one.
But to me, the real question is this: If the order of your tuples to don't matter, do you actually need tuples? There are other types in which the order of the elements in a container does not change the meaning; such as a set. You may want to use a Set from Data.Set, or you can define a pair type in which ordering doesn't matter. It will end up being a cardinality restricted set type though.
If you just want to get it working, here is some code for the first option:
nubSym :: Ord a => [(a,a)] -> [(a,a)] nubSym = nub . map fix where fix (a,b) | a > b = (b,a) fix p = p
Cheers, Ozgur
-- Ozgur Akgun
participants (4)
-
Daniel Fischer
-
edgar klerks
-
Martin Tomko
-
Ozgur Akgun