Most elegant funciton for removing adjacent duplicates from a list using foldl and foldr

I need to write an implementation using foldl, and a separate implementation using foldr, of a function, "remdups xs", that removes adjacent duplicate items from the list xs. For example, remdups [1,2,2,3,3,3,1,1]= [1,2,3,1]. My approach is first to write a direct recursion, as follows: remdups :: (Eq a) => [a] -> [a] remdups [] = [] remdups (x : []) = [x] remdups (x : xx : xs) = if x == xx then remdups (x : xs) else x : remdups (xx : xs) This code works, but it has three cases, not usual two, namely [] and (x : xs). What, if any, is the implementation using only two cases? Also, if three cases are required, then how can it be implemented using foldr, and how using foldl? Thanks. _________________________________________________________________ Express your personality in color! Preview and select themes for Hotmail®. http://www.windowslive-hotmail.com/LearnMore/personalize.aspx?ocid=TXT_MSGTX...

2009/3/15 R J
I need to write an implementation using foldl, and a separate implementation using foldr, of a function, "remdups xs", that removes adjacent duplicate items from the list xs. For example, remdups [1,2,2,3,3,3,1,1]= [1,2,3,1].
My approach is first to write a direct recursion, as follows:
remdups :: (Eq a) => [a] -> [a] remdups [] = [] remdups (x : []) = [x] remdups (x : xx : xs) = if x == xx then remdups (x : xs) else x : remdups (xx : xs)
This code works, but it has three cases, not usual two, namely [] and (x : xs).
What, if any, is the implementation using only two cases?
Also, if three cases are required, then how can it be implemented using foldr, and how using foldl?
Thanks.
Perhaps it would be helpful to define a helper function with this signature: prepend :: (Eq a) => a -> [a] -> [a] Which for "prepend x xs" will put x at the front of the list, so long as the first element of the list xs is different from x. Once you have this function, take a look at the type signature for foldr. -- Sebastian Sylvan +44(0)7857-300802 UIN: 44640862

2009/3/15 R J
What, if any, is the implementation using only two cases?
This version considers 2 cases 2 times :-) But only the 'go' function is recursive, so it could probably be written using some kind of fold. The value being build by the fold should probably be some kind of tuple so you can keep track of some state. remdups2 :: (Eq a) => [a] -> [a] remdups2 [] = [] remdups2 (x:xs) = go x xs where go x [] = [x] go x (y:ys) = if x == y then go x ys else x : go y ys I almost managed to write one using foldr, but it always put the first group last :-( Perhaps someone else manages to get it right. -- Warning: doesn't work correctly! Last group is last... remdups3 :: (Eq a) => [a] -> [a] remdups3 [] = [] remdups3 (x:xs) = snd $ foldr f (x, []) xs where f y (x, xs') = if y == x then (x, xs') else (y, x : xs')

Why don't you just swap the pattern match order?
remdups :: (Eq a) => [a] -> [a]
remdups (x : xx : xs) = if x == xx then remdups (x : xs) else x :
remdups (xx : xs)
remdups xs = xs
This should cover all cases no?
Also I prefer guards, but I guess that is personal
remdups (x1:x2:xs)
| x1 == x2 = remdups (x2 : xs)
| otherwise = x1 : remdups (x2 : xs)
remdups xs = xs
2009/3/15 R J
I need to write an implementation using foldl, and a separate implementation using foldr, of a function, "remdups xs", that removes adjacent duplicate items from the list xs. For example, remdups [1,2,2,3,3,3,1,1]= [1,2,3,1].
My approach is first to write a direct recursion, as follows:
remdups :: (Eq a) => [a] -> [a] remdups [] = [] remdups (x : []) = [x] remdups (x : xx : xs) = if x == xx then remdups (x : xs) else x : remdups (xx : xs)
This code works, but it has three cases, not usual two, namely [] and (x : xs).
What, if any, is the implementation using only two cases?
Also, if three cases are required, then how can it be implemented using foldr, and how using foldl?
Thanks.
------------------------------ Express your personality in color! Preview and select themes for Hotmail®. See how.http://www.windowslive-hotmail.com/LearnMore/personalize.aspx?ocid=TXT_MSGTX...
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

R J wrote:
I need to write an implementation using foldl, and a separate implementation using foldr, of a function, "remdups xs", that removes adjacent duplicate items from the list xs. For example, remdups [1,2,2,3,3,3,1,1]= [1,2,3,1].
My approach is first to write a direct recursion, as follows:
remdups :: (Eq a) => [a] -> [a] remdups [] = [] remdups (x : []) = [x] remdups (x : xx : xs) = if x == xx then remdups (x : xs) else x : remdups (xx : xs)
This code works, but it has three cases, not usual two, namely [] and (x : xs).
You should take a look at the page on declaration style vs expression style: http://haskell.org/haskellwiki/Declaration_vs._expression_style At the risk of doing homework, it is always the case that you can decompose complex pattern matching into basic pattern matching (which for lists means it always has two cases, since list has two constructors).[1] remdups [] = ...#1 remdups (x:[]) = ...#2 remdups (x:(xx:xs)) = ...#3 == {desugar pattern-matching into case} remdups = \a -> case a of [] -> ...#1 (x:[]) -> ...#2 (x:(xx:xs)) -> ...#3 == {desugar case into case} remdups = \a -> case a of [] -> ...#1 (x:b) -> case b of [] -> ...#2 (xx:xs) -> ...#3 This transformation explicitly gives a name to the second argument of the first (:) which is beneficial since it means you don't need to allocate a new one that's identical to the old one in order to pass to the recursion. For the Then we know x==xx therefore (x:xs) == (xx:xs), for the Else we need (xx:xs), in both cases we already have an (xx:xs) laying around, namely b. If you want to give a name like this without manually desugaring the case statements yourself, then you can use an as-pattern like (x: b@(xx:xs)) which will bind the variable b to the value (xx:xs) just like above. [1] This would not be true if, for example, the language could express non-linear terms like in Prolog and other logic languages. Pattern matching can still be decomposed in such languages, but they need to introduce unification constraints along with the smaller patterns, to ensure correctness of the transformation. -- Live well, ~wren
participants (5)
-
Peter Verswyvelen
-
R J
-
Roel van Dijk
-
Sebastian Sylvan
-
wren ng thornton