Difference between pages "User talk:Atravers" and "99 questions/Solutions/10"

From HaskellWiki
(Difference between pages)
Jump to navigation Jump to search
(Next response to HowardBGolden)
 
m (fix omission of function "group" in offered alternate list comprehension)
 
Line 1: Line 1:
  +
(*) Run-length encoding of a list.
== Thank You, Atravers! ==
 
I appreciate all your work on the wiki. Carry on! Please let me know if I can help in any way. —[[User:HowardBGolden|HowardBGolden]] ([[User talk:HowardBGolden|talk]]) 20:46, 14 March 2021 (UTC)
 
   
  +
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.
Thanks (I assume you're referring to what I've rewritten, rather than what I've wrote myself ;-). Considering just how much content is here, I didn't think I was making ''that'' much of a difference.<br>
 
I do have a question: has anyone [else] expressed an interest in using CommonMark here?
 
* I frequently type out CM formatting at first, only to then replace it with what the HsWiki uses now;
 
* Of course, if MediaWiki is already switching to CM, then the question is academic...
 
&mdash; [[User:Atravers|Atravers]] 12:37 15 March 2021 (UTC)
 
   
  +
<haskell>
:''(Note: Above reply from Atravers seems to have an incorrect timestamp) &mdash; s/b 15 March 2021 (UTC)''
 
  +
encode xs = map (\x -> (length x,head x)) (group xs)
:I don't recall anyone expressing an interest in using CommonMark. However, we haven't really solicited suggestions, so this isn't much indication of interest level.
 
  +
</haskell>
:At the moment, you might want to use [https://pandoc.org Pandoc] on your own computer to convert your CommonMark to MediaWiki and then paste it into wiki pages. Perhaps we can even set up a converter app on our server to do this. &mdash; [[User:HowardBGolden|HowardBGolden]] ([[User talk:HowardBGolden|talk]]) 18:02, 15 March 2021 (UTC)
 
   
  +
which can also be expressed as a list comprehension:
:''(Time corrected, again - problem with client, not HsWiki server >_< )''
 
  +
:Heh - I must be one of the few still doing this "directly" (no intervening tools like Pandoc) - I was just curious, considering CM has been around since (at least) 6 years.
 
  +
<haskell>
:Since no-one else has asked for it, I'll just leave it to MediaWiki to decide when/if CM support is added :-)
 
  +
[(length x, head x) | x <- group xs]
&mdash; [[User:Atravers|Atravers]] 20:40 15 March 2021 (UTC)
 
  +
</haskell>
  +
  +
or
  +
  +
<haskell>
  +
[(length (x:xs), x) | (x:xs) <- group xs]
  +
</haskell>
  +
  +
Or writing it [[Pointfree]] (Note that the type signature is essential here to avoid hitting the [[Monomorphism Restriction]]):
  +
  +
<haskell>
  +
encode :: Eq a => [a] -> [(Int, a)]
  +
encode = map (\x -> (length x, head x)) . group
  +
</haskell>
  +
  +
Or (ab)using the "&&&" arrow operator for tuples:
  +
  +
<haskell>
  +
encode :: Eq a => [a] -> [(Int, a)]
  +
encode xs = map (length &&& head) $ group xs
  +
</haskell>
  +
  +
Or using the slightly more verbose (w.r.t. <hask>(&&&)</hask>) Applicative combinators:
  +
  +
<haskell>
  +
encode :: Eq a => [a] -> [(Int, a)]
  +
encode = map ((,) <$> length <*> head) . pack
  +
</haskell>
  +
  +
Or with the help of foldr (''pack'' is the resulting function from P09):
  +
  +
<haskell>
  +
encode xs = (enc . pack) xs
  +
where enc = foldr (\x acc -> (length x, head x) : acc) []
  +
</haskell>
  +
  +
Or using takeWhile and dropWhile:
  +
  +
<haskell>
  +
encode [] = []
  +
encode (x:xs) = (length $ x : takeWhile (==x) xs, x)
  +
: encode (dropWhile (==x) xs)
  +
</haskell>
  +
  +
Or without higher order functions:
  +
  +
<haskell>
  +
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
  +
</haskell>
  +
  +
Or we can make use of zip and group:
  +
  +
<haskell>
  +
import List
  +
encode :: Eq a => [a] -> [(Int, a)]
  +
encode xs=zip (map length l) h where
  +
l = (group xs)
  +
h = map head l
  +
</haskell>
  +
  +
Or if we ignore the rule that we should use the result of P09,
  +
  +
<haskell>
  +
encode :: Eq a => [a] -> [(Int,a)]
  +
encode xs = foldr f final xs Nothing
  +
where
  +
f x r (Just a@(i,q)) | x == q = r (Just (i+1,q))
  +
| otherwise = a : r (Just (1, x))
  +
f x r Nothing = r (Just (1, x))
  +
  +
final (Just a@(i,q)) = [a]
  +
final Nothing = []
  +
</haskell>
  +
  +
which can become a good transformer for list fusion like so:
  +
  +
<haskell>
  +
{-# INLINE encode #-}
  +
encode :: Eq a => [a] -> [(Int,a)]
  +
encode xs = build (\c n ->
  +
let
  +
f x r (Just a@(i,q)) | x == q = r (Just (i+1,q))
  +
| otherwise = a `c` r (Just (1, x))
  +
f x r Nothing = r (Just (1, x))
  +
  +
final (Just a@(i,q)) = a `c` n
  +
final Nothing = n
  +
  +
in
  +
foldr f final xs Nothing)
  +
</haskell>
  +
  +
Just one more way with recursion:
  +
  +
<haskell>
  +
encode :: [[t]] -> [(Int, t)]
  +
encode = let f acc [] = acc
  +
f acc (x:xs) = f ((length x, head x): acc) xs
  +
in reverse . f []
  +
</haskell>
  +
  +
  +
[[Category:Programming exercise spoilers]]

Latest revision as of 03:45, 19 May 2021

(*) 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

[(length (x:xs), x) | (x:xs) <- 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

Or if we ignore the rule that we should use the result of P09,

encode :: Eq a => [a] -> [(Int,a)]
encode xs = foldr f final xs Nothing
  where
    f x r (Just a@(i,q)) | x == q = r (Just (i+1,q))
                         | otherwise = a : r (Just (1, x))
    f x r Nothing = r (Just (1, x))

    final (Just a@(i,q)) = [a]
    final Nothing = []

which can become a good transformer for list fusion like so:

{-# INLINE encode #-}
encode :: Eq a => [a] -> [(Int,a)]
encode xs = build (\c n ->
  let
    f x r (Just a@(i,q)) | x == q = r (Just (i+1,q))
                         | otherwise = a `c` r (Just (1, x))
    f x r Nothing = r (Just (1, x))

    final (Just a@(i,q)) = a `c` n
    final Nothing = n

  in
    foldr f final xs Nothing)

Just one more way with recursion:

encode :: [[t]] -> [(Int, t)]
encode =  let f acc [] = acc
              f acc (x:xs) = f ((length x, head x): acc) xs
          in  reverse . f []