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

From HaskellWiki
Jump to navigation Jump to search
(Fix a typo.)
(Added another solution)
 
(5 intermediate revisions by 4 users not shown)
Line 24: Line 24:
 
<haskell>
 
<haskell>
 
toTuple :: ListItem a -> (Int, a)
 
toTuple :: ListItem a -> (Int, a)
toTuple (Single x) = (1, x)
+
toTuple (Single x) = (1, x)
 
toTuple (Multiple n x) = (n, x)
 
toTuple (Multiple n x) = (n, x)
 
</haskell>
 
</haskell>
Line 31: Line 31:
   
 
<haskell>
 
<haskell>
decode :: [ListItem a] -> [a]
+
decodeModified :: [ListItem a] -> [a]
decode = concatMap (uncurry replicate . toTuple)
+
decodeModified = concatMap (uncurry replicate . toTuple)
 
</haskell>
 
</haskell>
   
 
a naïve solution with <hask>foldl</hask>:
 
a naïve solution with <hask>foldl</hask>:
 
<haskell>
 
<haskell>
decode :: [ListItem a]-> [a]
+
decodeModified :: [ListItem a]-> [a]
decode = foldl (\x y -> x ++ decodeHelper y) []
+
decodeModified = foldl (\x y -> x ++ decodeHelper y) []
 
where
 
where
 
decodeHelper :: ListItem a -> [a]
 
decodeHelper :: ListItem a -> [a]
decodeHelper (Single x)=[x]
+
decodeHelper (Single x) = [x]
decodeHelper (Multiple n x)= replicate n x
+
decodeHelper (Multiple n x) = replicate n x
 
</haskell>
 
</haskell>
   
 
<hask>foldl</hask> can also be used to solve this problem:
 
<hask>foldl</hask> can also be used to solve this problem:
   
  +
<haskell>
  +
decodeModified :: [ListItem a] -> [a]
 
decodeModified = foldl (\acc e -> case e of Single x -> acc ++ [x]; Multiple n x -> acc ++ replicate n x) []
  +
</haskell>
  +
  +
  +
Another way to decode the simplified encoding (which encoding, in the opinion of this editor, is a far more sensible one for Haskell):
  +
  +
<haskell>
  +
decode :: Eq a => [(Int,a)] -> [a]
  +
decode xs = foldr f [] xs
  +
where
  +
f (1, x) r = x : r
  +
f (k, x) r = x : f (k-1, x) r
  +
</haskell>
  +
  +
Or, to make it a good transformer for list fusion,
  +
  +
<haskell>
  +
{-# INLINE decode #-}
  +
decode :: Eq a => [(Int,a)] -> [a]
  +
decode xs = build (\c n ->
  +
let
  +
f (1, x) r = x `c` r
  +
f (k, x) r = x `c` f (k-1, x) r
  +
in
  +
foldr f n xs)
  +
</haskell>
  +
  +
A solution from first principles:
 
<haskell>
 
<haskell>
 
decode :: [ListItem a] -> [a]
 
decode :: [ListItem a] -> [a]
  +
decode [] = []
decode = foldl (\acc e -> case e of Single x -> acc ++ [x]; Multiple n x -> acc ++ replicate n x) []
 
  +
decode ((Single x):xs) = x:decode xs
  +
decode ((Multiple 2 x):xs) = x:x:decode xs
  +
decode ((Multiple n x):xs) = x:decode ((Multiple (n-1) x):xs)
 
</haskell>
 
</haskell>
  +
  +
[[Category:Programming exercise spoilers]]

Latest revision as of 17:33, 13 June 2020

(**) Decode a run-length encoded list.

Given a run-length code list generated as specified in problem 11. Construct its uncompressed version.

decodeModified :: [ListItem a] -> [a]
decodeModified = concatMap decodeHelper
    where
      decodeHelper (Single x)     = [x]
      decodeHelper (Multiple n x) = replicate n x

We only need to map single instances of an element to a list containing only one element and multiple ones to a list containing the specified number of elements and concatenate these lists.

A solution for the simpler encoding from problem 10 can be given as:

decode :: [(Int, a)] -> [a]
decode = concatMap (uncurry replicate)

This can be easily extended given a helper function:

toTuple :: ListItem a -> (Int, a)
toTuple (Single x)     = (1, x)
toTuple (Multiple n x) = (n, x)

as:

decodeModified :: [ListItem a] -> [a]
decodeModified = concatMap (uncurry replicate . toTuple)

a naïve solution with foldl:

decodeModified :: [ListItem a]-> [a]
decodeModified = foldl (\x y -> x ++ decodeHelper y) []
    where
        decodeHelper :: ListItem a -> [a]
        decodeHelper (Single x)     = [x]
        decodeHelper (Multiple n x) = replicate n x

foldl can also be used to solve this problem:

decodeModified :: [ListItem a] -> [a]
decodeModified = foldl (\acc e -> case e of Single x -> acc ++ [x]; Multiple n x -> acc ++ replicate n x) []


Another way to decode the simplified encoding (which encoding, in the opinion of this editor, is a far more sensible one for Haskell):

decode :: Eq a => [(Int,a)] -> [a]
decode xs = foldr f [] xs
  where
    f (1, x) r = x : r
    f (k, x) r = x : f (k-1, x) r

Or, to make it a good transformer for list fusion,

{-# INLINE decode #-}
decode :: Eq a => [(Int,a)] -> [a]
decode xs = build (\c n ->
  let
    f (1, x) r = x `c` r
    f (k, x) r = x `c` f (k-1, x) r
  in
    foldr f n xs)

A solution from first principles:

decode :: [ListItem a] -> [a]
decode [] = []
decode ((Single x):xs) = x:decode xs
decode ((Multiple 2 x):xs) = x:x:decode xs
decode ((Multiple n x):xs) = x:decode ((Multiple (n-1) x):xs)