99 questions/Solutions/10

From HaskellWiki
< 99 questions‎ | Solutions
Revision as of 11:23, 26 July 2012 by Wi (talk | contribs)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

(*) Run-length encoding of a list.

Use the result of problem P09 to implement the so-called run-length encoding data compression method. Consecutive duplicates of elements are encoded as lists (N E) where N is the number of duplicates of the element E.

encode xs = map (\x -> (length x,head x)) (group xs)

which can also be expressed as a list comprehension:

[(length x, head x) | x <- group xs]

Or writing it Pointfree (Note that the type signature is essential here to avoid hitting the Monomorphism Restriction):

encode :: Eq a => [a] -> [(Int, a)]
encode = map (\x -> (length x, head x)) . group

Or (ab)using the "&&&" arrow operator for tuples:

encode :: Eq a => [a] -> [(Int, a)]
encode xs = map (length &&& head) $ group xs

Or using the slightly more verbose (w.r.t. (&&&)) Applicative combinators:

encode :: Eq a => [a] -> [(Int, a)]
encode = map ((,) <$> length <*> head) . pack

Or with the help of foldr (pack is the resulting function from P09):

encode xs = (enc . pack) xs
	where enc = foldr (\x acc -> (length x, head x) : acc) []

Or using takeWhile and dropWhile:

encode [] = []
encode (x:xs) = (length $ x : takeWhile (==x) xs, x)
                 : encode (dropWhile (==x) xs)

Or without higher order functions:

encode []     = []
encode (x:xs) = encode' 1 x xs where
    encode' n x [] = [(n, x)]
    encode' n x (y:ys)
        | x == y    = encode' (n + 1) x ys
        | otherwise = (n, x) : encode' 1 y ys

Or we can make use of zip and group:

 
import List
encode :: Eq a => [a] -> [(Int, a)]
encode xs=zip (map length l) h where 
    l = (group xs)
    h = map head l