Difference between revisions of "99 questions/11 to 20"

From HaskellWiki
Jump to navigation Jump to search
(Added a solution to Problem 18)
(moved solutions to subpages of 99 questions/Solutions, reformatted code examples)
Line 5: Line 5:
 
== Problem 11 ==
 
== Problem 11 ==
   
(*) Modified run-length encoding.
+
(*) Modified run-length encoding.
  +
 
Modify the result of problem 10 in such a way that if an element has no duplicates it is simply copied into the result list. Only elements with duplicates are transferred as (N E) lists.
 
Modify the result of problem 10 in such a way that if an element has no duplicates it is simply copied into the result list. Only elements with duplicates are transferred as (N E) lists.
   
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (encode-modified '(a a a a b c c a a d e e e e))
 
* (encode-modified '(a a a a b c c a a d e e e e))
 
((4 A) B (2 C) (2 A) D (4 E))
 
((4 A) B (2 C) (2 A) D (4 E))
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
P11> encodeModified "aaaabccaadeeee"
 
[Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
P11> encodeModified "aaaabccaadeeee"
data ListItem a = Single a | Multiple Int a
 
  +
[Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']
deriving (Show)
 
 
encodeModified :: Eq a => [a] -> [ListItem a]
 
encodeModified = map encodeHelper . encode
 
where
 
encodeHelper (1,x) = Single x
 
encodeHelper (n,x) = Multiple n x
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/11 | Solutions]]
Again, like in problem 7, we need a utility type because lists in haskell are homogeneous. Afterwards we use the <hask>encode</hask> function from problem 10 and map single instances of a list item to <hask>Single</hask> and multiple ones to <hask>Multiple</hask>.
 
   
The ListItem definition contains 'deriving (Show)' so that we can get interactive output.
 
 
 
 
== Problem 12 ==
 
== Problem 12 ==
   
(**) Decode a run-length encoded list.
+
(**) Decode a run-length encoded list.
  +
 
Given a run-length code list generated as specified in problem 11. Construct its uncompressed version.
 
Given a run-length code list generated as specified in problem 11. Construct its uncompressed version.
   
<pre>
 
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
P12> decodeModified [Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']
 
P12> decodeModified [Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']
 
"aaaabccaadeeee"
 
"aaaabccaadeeee"
</pre>
 
 
Solution:
 
<haskell>
 
decodeModified :: [ListItem a] -> [a]
 
decodeModified = concatMap decodeHelper
 
where
 
decodeHelper (Single x) = [x]
 
decodeHelper (Multiple n x) = replicate n x
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/12 | Solutions]]
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.
 
  +
 
 
 
== Problem 13 ==
 
== Problem 13 ==
   
 
(**) Run-length encoding of a list (direct solution).
 
(**) Run-length encoding of a list (direct solution).
  +
 
Implement the so-called run-length encoding data compression method directly. I.e. don't explicitly create the sublists containing the duplicates, as in problem 9, but only count them. As in problem P11, simplify the result list by replacing the singleton lists (1 X) by X.
 
Implement the so-called run-length encoding data compression method directly. I.e. don't explicitly create the sublists containing the duplicates, as in problem 9, but only count them. As in problem P11, simplify the result list by replacing the singleton lists (1 X) by X.
   
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (encode-direct '(a a a a b c c a a d e e e e))
 
* (encode-direct '(a a a a b c c a a d e e e e))
 
((4 A) B (2 C) (2 A) D (4 E))
 
((4 A) B (2 C) (2 A) D (4 E))
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
P13> encodeDirect "aaaabccaadeeee"
 
P13> encodeDirect "aaaabccaadeeee"
 
[Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']
 
[Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']
</pre>
+
</haskell>
   
  +
[[99 questions/Solutions/13 | Solutions]]
Solution:
 
<haskell>
 
encode' :: Eq a => [a] -> [(Int,a)]
 
encode' = foldr helper []
 
where
 
helper x [] = [(1,x)]
 
helper x (y@(a,b):ys)
 
| x == b = (1+a,x):ys
 
| otherwise = (1,x):y:ys
 
   
encodeDirect :: Eq a => [a] -> [ListItem a]
 
encodeDirect = map encodeHelper . encode'
 
where
 
encodeHelper (1,x) = Single x
 
encodeHelper (n,x) = Multiple n x
 
</haskell>
 
   
First of all we could rewrite the function <hask>encode</hask> from problem 10 in a way that is does not create the sublists. Thus, I decided to traverse the original list from right to left (using <hask>foldr</hask>) and to prepend each element to the resulting list in the proper way. Thereafter we only need to modify the function <hask>encodeModified</hask> from problem 11 to use <hask>encode'</hask>.
 
 
 
== Problem 14 ==
 
== Problem 14 ==
   
 
(*) Duplicate the elements of a list.
 
(*) Duplicate the elements of a list.
  +
  +
Example:
   
 
<pre>
 
<pre>
Example:
 
 
* (dupli '(a b c c d))
 
* (dupli '(a b c c d))
 
(A A B B C C C C D D)
 
(A A B B C C C C D D)
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
> dupli [1, 2, 3]
 
> dupli [1, 2, 3]
 
[1,1,2,2,3,3]
 
[1,1,2,2,3,3]
</pre>
 
 
Solution:
 
<haskell>
 
dupli [] = []
 
dupli (x:xs) = x:x:dupli xs
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/14 | Solutions]]
or, using list comprehension syntax:
 
   
<haskell>
 
dupli list = concat [[x,x] | x <- list]
 
</haskell>
 
 
or, using the list monad:
 
<haskell>
 
dupli xs = xs >>= (\x -> [x,x])
 
</haskell>
 
 
or, using concatMap:
 
<haskell>
 
dupli = concatMap (\x -> [x,x])
 
</haskell>
 
 
also using concatMap:
 
<haskell>
 
dupli = concatMap (replicate 2)
 
</haskell>
 
 
or, using foldr:
 
<haskell>
 
dupli = foldr (\ x xs -> x : x : xs) []
 
</haskell>
 
   
 
== Problem 15 ==
 
== Problem 15 ==
   
 
(**) Replicate the elements of a list a given number of times.
 
(**) Replicate the elements of a list a given number of times.
  +
  +
Example:
   
 
<pre>
 
<pre>
Example:
 
 
* (repli '(a b c) 3)
 
* (repli '(a b c) 3)
 
(A A A B B B C C C)
 
(A A A B B B C C C)
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
> repli "abc" 3
 
"aaabbbccc"
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
> repli "abc" 3
repli :: [a] -> Int -> [a]
 
  +
"aaabbbccc"
repli xs n = concatMap (replicate n) xs
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/15 | Solutions]]
or, in Pointfree style:
 
  +
<haskell>
 
repli = flip $ concatMap . replicate
 
</haskell>
 
   
 
== Problem 16 ==
 
== Problem 16 ==
  +
 
(**) Drop every N'th element from a list.
 
(**) Drop every N'th element from a list.
   
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (drop '(a b c d e f g h i k) 3)
 
* (drop '(a b c d e f g h i k) 3)
 
(A B D E G H K)
 
(A B D E G H K)
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
*Main> dropEvery "abcdefghik" 3
 
*Main> dropEvery "abcdefghik" 3
 
"abdeghk"
 
"abdeghk"
</pre>
 
 
Solution:
 
<haskell>
 
dropEvery :: [a] -> Int -> [a]
 
dropEvery [] _ = []
 
dropEvery (x:xs) n = dropEvery' (x:xs) n 1 where
 
dropEvery' (x:xs) n i = (if (n `divides` i) then
 
[] else
 
[x])
 
++ (dropEvery' xs n (i+1))
 
dropEvery' [] _ _ = []
 
divides x y = y `mod` x == 0
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/16 | Solutions]]
or an alternative iterative solution:
 
<haskell>
 
dropEvery :: [a] -> Int -> [a]
 
dropEvery list count = helper list count count
 
where helper [] _ _ = []
 
helper (x:xs) count 1 = helper xs count count
 
helper (x:xs) count n = x : (helper xs count (n - 1))
 
</haskell>
 
   
or yet another iterative solution which divides lists using Prelude:
 
<haskell>
 
dropEvery :: [a] -> Int -> [a]
 
dropEvery [] _ = []
 
dropEvery list count = (take (count-1) list) ++ dropEvery (drop count list) count
 
</haskell>
 
 
or using zip:
 
<haskell>
 
dropEvery n = map snd . filter ((n/=) . fst) . zip (cycle [1..n])
 
</haskell>
 
 
 
 
== Problem 17 ==
 
== Problem 17 ==
Line 213: Line 133:
   
 
Do not use any predefined predicates.
 
Do not use any predefined predicates.
  +
  +
Example:
   
 
<pre>
 
<pre>
Example:
 
 
* (split '(a b c d e f g h i k) 3)
 
* (split '(a b c d e f g h i k) 3)
 
( (A B C) (D E F G H I K))
 
( (A B C) (D E F G H I K))
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
*Main> split "abcdefghik" 3
 
*Main> split "abcdefghik" 3
 
("abc", "defghik")
 
("abc", "defghik")
</pre>
 
 
Solution using take and drop:
 
<haskell>
 
split xs n = (take n xs, drop n xs)
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/17 | Solutions]]
Alternatively, we have the following recursive solution:
 
<haskell>
 
split :: [a] -> Int -> ([a], [a])
 
split [] _ = ([], [])
 
split l@(x : xs) n | n > 0 = (x : ys, zs)
 
| otherwise = ([], l)
 
where (ys,zs) = split xs (n - 1)
 
</haskell>
 
   
The same solution as above written more cleanly:
 
<haskell>
 
split :: [a] -> Int -> ([a], [a])
 
split xs 0 = ([], xs)
 
split (x:xs) n = let (f,l) = split xs (n-1) in (x : f, l)
 
</haskell>
 
   
Note that this function, with the parameters in the other order, exists as <hask>splitAt</hask>.
 
 
 
 
== Problem 18 ==
 
== Problem 18 ==
   
Line 253: Line 156:
   
 
Given two indices, i and k, the slice is the list containing the elements between the i'th and k'th element of the original list (both limits included). Start counting the elements with 1.
 
Given two indices, i and k, the slice is the list containing the elements between the i'th and k'th element of the original list (both limits included). Start counting the elements with 1.
  +
  +
Example:
   
 
<pre>
 
<pre>
Example:
 
 
* (slice '(a b c d e f g h i k) 3 7)
 
* (slice '(a b c d e f g h i k) 3 7)
 
(C D E F G)
 
(C D E F G)
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
*Main> slice ['a','b','c','d','e','f','g','h','i','k'] 3 7
 
*Main> slice ['a','b','c','d','e','f','g','h','i','k'] 3 7
 
"cdefg"
 
"cdefg"
</pre>
 
 
Solution:
 
<haskell>
 
slice xs (i+1) k = take (k-i) $ drop i xs
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/18 | Solutions]]
Or, an iterative solution:
 
<haskell>
 
slice :: [a]->Int->Int->[a]
 
slice lst 1 m = slice' lst m []
 
where
 
slice' :: [a]->Int->[a]->[a]
 
slice' _ 0 acc = reverse acc
 
slice' (x:xs) n acc = slice' xs (n - 1) (x:acc)
 
slice (x:xs) n m = slice xs (n - 1) (m - 1)
 
</haskell>
 
   
Or:
 
 
<haskell>
 
slice :: [a] -> Int -> Int -> [a]
 
slice (x:xs) i k
 
| i > 1 = slice xs (i - 1) (k - 1)
 
| k < 1 = []
 
| otherwise = x:slice xs (i - 1) (k - 1)
 
</haskell>
 
   
 
== Problem 19 ==
 
== Problem 19 ==
Line 295: Line 179:
   
 
Hint: Use the predefined functions length and (++).
 
Hint: Use the predefined functions length and (++).
  +
  +
Examples:
   
 
<pre>
 
<pre>
Examples:
 
 
* (rotate '(a b c d e f g h) 3)
 
* (rotate '(a b c d e f g h) 3)
 
(D E F G H A B C)
 
(D E F G H A B C)
Line 303: Line 188:
 
* (rotate '(a b c d e f g h) -2)
 
* (rotate '(a b c d e f g h) -2)
 
(G H A B C D E F)
 
(G H A B C D E F)
  +
</pre>
   
 
Examples in Haskell:
 
Examples in Haskell:
  +
  +
<haskell>
 
*Main> rotate ['a','b','c','d','e','f','g','h'] 3
 
*Main> rotate ['a','b','c','d','e','f','g','h'] 3
 
"defghabc"
 
"defghabc"
Line 310: Line 198:
 
*Main> rotate ['a','b','c','d','e','f','g','h'] (-2)
 
*Main> rotate ['a','b','c','d','e','f','g','h'] (-2)
 
"ghabcdef"
 
"ghabcdef"
</pre>
 
 
Solution:
 
<haskell>
 
rotate [] _ = []
 
rotate l 0 = l
 
rotate (x:xs) (n+1) = rotate (xs ++ [x]) n
 
rotate l n = rotate l (length l + n)
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/19 | Solutions]]
There are two separate cases:
 
* If n > 0, move the first element to the end of the list n times.
 
* If n < 0, convert the problem to the equivalent problem for n > 0 by adding the list's length to n.
 
   
or using cycle:
 
<haskell>
 
rotate xs n = take len . drop (n `mod` len) . cycle $ xs
 
where len = length xs
 
</haskell>
 
 
or
 
 
<haskell>
 
rotate xs n = if n >= 0 then
 
drop n xs ++ take n xs
 
else let l = ((length xs) + n) in
 
drop l xs ++ take l xs
 
</haskell>
 
 
or
 
 
<haskell>
 
rotate xs n = drop nn xs ++ take nn xs
 
where
 
nn = n `mod` length xs
 
</haskell>
 
 
 
 
== Problem 20 ==
 
== Problem 20 ==
Line 352: Line 208:
   
 
Example in Prolog:
 
Example in Prolog:
  +
 
<pre>
 
<pre>
 
?- remove_at(X,[a,b,c,d],2,R).
 
?- remove_at(X,[a,b,c,d],2,R).
Line 359: Line 216:
   
 
Example in Lisp:
 
Example in Lisp:
  +
 
<pre>
 
<pre>
 
* (remove-at '(a b c d) 2)
 
* (remove-at '(a b c d) 2)
 
(A C D)
 
(A C D)
 
</pre>
 
</pre>
  +
 
(Note that this only returns the residue list, while the Prolog version also returns the deleted element.)
 
(Note that this only returns the residue list, while the Prolog version also returns the deleted element.)
   
 
Example in Haskell:
 
Example in Haskell:
  +
<pre>
 
  +
<haskell>
 
*Main> removeAt 1 "abcd"
 
*Main> removeAt 1 "abcd"
 
('b',"acd")
 
('b',"acd")
</pre>
 
 
Solution:
 
<haskell>
 
removeAt :: Int -> [a] -> (a, [a])
 
removeAt k xs = case back of
 
[] -> error "removeAt: index too large"
 
x:rest -> (x, front ++ rest)
 
where (front, back) = splitAt k xs
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/20 | Solutions]]
Simply use the <hask>splitAt</hask> to split after k elements.
 
If the original list has fewer than k+1 elements, the second list will be empty, and there will be no element to extract.
 
Note that the Prolog and Lisp versions treat 1 as the first element in the list, and the Lisp version appends NIL elements to the end of the list if k is greater than the list length.
 
   
or
 
 
<haskell>
 
removeAt n xs = (xs!!n,take n xs ++ drop (n+1) xs)
 
</haskell>
 
   
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Revision as of 15:51, 13 July 2010


This is part of Ninety-Nine Haskell Problems, based on Ninety-Nine Prolog Problems and Ninety-Nine Lisp Problems.

Problem 11

(*) Modified run-length encoding.

Modify the result of problem 10 in such a way that if an element has no duplicates it is simply copied into the result list. Only elements with duplicates are transferred as (N E) lists.

Example:

* (encode-modified '(a a a a b c c a a d e e e e))
((4 A) B (2 C) (2 A) D (4 E))

Example in Haskell:

P11> encodeModified "aaaabccaadeeee"
[Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']

Solutions


Problem 12

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

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

Example in Haskell:

P12> decodeModified [Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']
"aaaabccaadeeee"

Solutions


Problem 13

(**) Run-length encoding of a list (direct solution).

Implement the so-called run-length encoding data compression method directly. I.e. don't explicitly create the sublists containing the duplicates, as in problem 9, but only count them. As in problem P11, simplify the result list by replacing the singleton lists (1 X) by X.

Example:

* (encode-direct '(a a a a b c c a a d e e e e))
((4 A) B (2 C) (2 A) D (4 E))

Example in Haskell:

P13> encodeDirect "aaaabccaadeeee"
[Multiple 4 'a',Single 'b',Multiple 2 'c',Multiple 2 'a',Single 'd',Multiple 4 'e']

Solutions


Problem 14

(*) Duplicate the elements of a list.

Example:

* (dupli '(a b c c d))
(A A B B C C C C D D)

Example in Haskell:

> dupli [1, 2, 3]
[1,1,2,2,3,3]

Solutions


Problem 15

(**) Replicate the elements of a list a given number of times.

Example:

* (repli '(a b c) 3)
(A A A B B B C C C)

Example in Haskell:

> repli "abc" 3
"aaabbbccc"

Solutions


Problem 16

(**) Drop every N'th element from a list.

Example:

* (drop '(a b c d e f g h i k) 3)
(A B D E G H K)

Example in Haskell:

*Main> dropEvery "abcdefghik" 3
"abdeghk"

Solutions


Problem 17

(*) Split a list into two parts; the length of the first part is given.

Do not use any predefined predicates.

Example:

* (split '(a b c d e f g h i k) 3)
( (A B C) (D E F G H I K))

Example in Haskell:

*Main> split "abcdefghik" 3
("abc", "defghik")

Solutions


Problem 18

(**) Extract a slice from a list.

Given two indices, i and k, the slice is the list containing the elements between the i'th and k'th element of the original list (both limits included). Start counting the elements with 1.

Example:

* (slice '(a b c d e f g h i k) 3 7)
(C D E F G)

Example in Haskell:

*Main> slice ['a','b','c','d','e','f','g','h','i','k'] 3 7
"cdefg"

Solutions


Problem 19

(**) Rotate a list N places to the left.

Hint: Use the predefined functions length and (++).

Examples:

* (rotate '(a b c d e f g h) 3)
(D E F G H A B C)

* (rotate '(a b c d e f g h) -2)
(G H A B C D E F)

Examples in Haskell:

*Main> rotate ['a','b','c','d','e','f','g','h'] 3
"defghabc"

*Main> rotate ['a','b','c','d','e','f','g','h'] (-2)
"ghabcdef"

Solutions


Problem 20

(*) Remove the K'th element from a list.

Example in Prolog:

?- remove_at(X,[a,b,c,d],2,R).
X = b
R = [a,c,d]

Example in Lisp:

* (remove-at '(a b c d) 2)
(A C D)

(Note that this only returns the residue list, while the Prolog version also returns the deleted element.)

Example in Haskell:

*Main> removeAt 1 "abcd"
('b',"acd")

Solutions