Difference between revisions of "99 questions/Solutions/8"

From HaskellWiki
Jump to navigation Jump to search
m (Pointed to the correct module in which group is defined)
m
(22 intermediate revisions by 15 users not shown)
Line 7: Line 7:
   
 
We simply group equal values together (using Data.List.group), then take the head of each.
 
We simply group equal values together (using Data.List.group), then take the head of each.
  +
Note that (with GHC) we must give an explicit type to ''compress'' otherwise we get:
 
 
An alternative solution is
   
 
<haskell>
 
<haskell>
 
compress (x:ys@(y:_))
Ambiguous type variable `a' in the constraint:
 
`Eq a'
+
| x == y = compress ys
  +
| otherwise = x : compress ys
arising from use of `group'
 
  +
compress ys = ys
Possible cause: the monomorphism restriction applied to the following:
 
  +
</haskell><br>
compress :: [a] -> [a]
 
  +
Probable fix: give these definition(s) an explicit type signature
 
  +
A variation of the above using <hask>foldr</hask> (note that GHC erases the <hask>Maybe</hask>s, producing efficient code):
or use -fno-monomorphism-restriction
 
  +
<haskell>
  +
compress xs = foldr f (const []) xs Nothing
  +
where
  +
f x r a@(Just q) | x == q = r a
  +
f x r _ = x : r (Just x)
 
</haskell>
 
</haskell>
   
  +
Another possibility using foldr (this one is not so efficient, because it pushes the whole input onto the "stack" before doing anything else):
We can circumvent the monomorphism restriction by writing ''compress'' this way (See: section 4.5.4 of [http://haskell.org/onlinereport the report]):
 
   
  +
<haskell>
<haskell>compress xs = map head $ group xs</haskell>
 
  +
compress :: (Eq a) => [a] -> [a]
  +
compress = foldr skipDups []
  +
where skipDups x [] = [x]
  +
skipDups x acc
  +
| x == head acc = acc
  +
| otherwise = x : acc
  +
</haskell>
   
  +
A very simple approach:
An alternative solution is
 
  +
  +
<haskell>
  +
compress [] = []
  +
compress (x:xs) = x : (compress $ dropWhile (== x) xs)
  +
</haskell>
  +
  +
Another approach, using foldr
  +
  +
<haskell>
  +
compress :: Eq a => [a] -> [a]
  +
compress x = foldr (\a b -> if a == (head b) then b else a:b) [last x] x
  +
</haskell>
  +
  +
Wrong solution using foldr
  +
<haskell>
  +
compress :: Eq a => [a] -> [a]
  +
compress xs = foldr (\x acc -> if x `elem` acc then acc else x:acc) [] xs
  +
-- Main> compress [1, 1, 1, 2, 2, 1, 1]
  +
-- [2,1] - must be [1,2,1]
  +
</haskell>
  +
  +
  +
and using foldl
  +
  +
<haskell>
  +
compress :: (Eq a) => [a] -> [a]
  +
compress x = foldl (\a b -> if (last a) == b then a else a ++ [b]) [head x] x
  +
compress' x = reverse $ foldl (\a b -> if (head a) == b then a else b:a) [head x] x
  +
</haskell>
  +
  +
A crazy variation that acts as a good transformer for fold/build fusion
   
 
<haskell>
 
<haskell>
  +
{-# INLINE compress #-}
compress [] = []
 
compress [a] = [a]
+
compress :: Eq a => [a] -> [a]
compress (x : y : xs) = (if x == y then [] else [x]) ++ compress (y : xs)
+
compress xs = build (\c n ->
  +
let
  +
f x r a@(Just q) | x == q = r a
  +
f x r _ = x `c` r (Just x)
  +
in
  +
foldr f (const n) xs Nothing)
 
</haskell>
 
</haskell>
  +
<br>
  +
[[Category:Programming exercise spoilers]]

Revision as of 13:44, 15 February 2015

(**) Eliminate consecutive duplicates of list elements.

compress :: Eq a => [a] -> [a]
compress = map head . group

We simply group equal values together (using Data.List.group), then take the head of each.

An alternative solution is

compress (x:ys@(y:_))
    | x == y    = compress ys
    | otherwise = x : compress ys
compress ys = ys

A variation of the above using foldr (note that GHC erases the Maybes, producing efficient code):

compress xs = foldr f (const []) xs Nothing
  where
    f x r a@(Just q) | x == q = r a
    f x r _ = x : r (Just x)

Another possibility using foldr (this one is not so efficient, because it pushes the whole input onto the "stack" before doing anything else):

compress :: (Eq a) => [a] -> [a]
compress = foldr skipDups []
    where skipDups x [] = [x]
          skipDups x acc
                | x == head acc = acc
                | otherwise = x : acc

A very simple approach:

compress []     = []
compress (x:xs) = x : (compress $ dropWhile (== x) xs)

Another approach, using foldr

compress :: Eq a => [a] -> [a]
compress x = foldr (\a b -> if a == (head b) then b else a:b) [last x] x

Wrong solution using foldr

compress :: Eq a => [a] -> [a]
compress xs = foldr (\x acc -> if x `elem` acc then acc else x:acc) [] xs
-- Main> compress [1, 1, 1, 2, 2, 1, 1]
-- [2,1] - must be [1,2,1]


and using foldl

compress :: (Eq a) => [a] -> [a]
compress x = foldl (\a b -> if (last a) == b then a else a ++ [b]) [head x] x
compress' x = reverse $ foldl (\a b -> if (head a) == b then a else b:a) [head x] x

A crazy variation that acts as a good transformer for fold/build fusion

{-# INLINE compress #-}
compress :: Eq a => [a] -> [a]
compress xs = build (\c n ->
  let
    f x r a@(Just q) | x == q = r a
    f x r _ = x `c` r (Just x)
  in
    foldr f (const n) xs Nothing)