99 questions/11 to 20

From HaskellWiki
< 99 questions
Revision as of 17:52, 12 December 2006 by JohannesAhlmann (talk | contribs) (problem 16 using zip)
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.


These are Haskell translations of Ninety Nine Lisp Problems.

If you want to work on one of these, put your name in the block so we know someone's working on it. Then, change n in your block to the appropriate problem number, and fill in the <Problem description>,<example in lisp>,<example in Haskell>,<solution in haskell> and <description of implementation> fields.


Problem 11

(*) Modified run-length encoding. Modify the result of problem P10 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']

Solution:

data ListItem a = Single a | Multiple Int a

encodeModified :: Eq a => [a] -> [ListItem a]
encodeModified = map encodeHelper . encode
    where
      encodeHelper (1,x) = Single x
      encodeHelper (n,x) = Multiple n x

Again, like in problem 7, we need a utility type because lists in haskell are homogeneous. Afterwards we use the encode function from problem 10 and map single instances of a list item to Single and multiple ones to Multiple.

Problem 12

(**) Decode a run-length encoded list. Given a run-length code list generated as specified in problem P11. 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"

Solution:

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.

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 P09, 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']

Solution:

encode' :: Eq a => [a] -> [(Int,a)]
encode' = foldr helper []
    where
      helper x [] = [(1,x)]
      helper x (y:ys)
        | x == snd y   = (1+fst y,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

First of all we could rewrite the function encode 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 foldr) and to prepend each element to the resulting list in the proper way. Thereafter we only need to modify the function encodeModified from problem 11 to use encode'.

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]

Solution:

dupli [] = []
dupli (x:xs) = x:x:dupli xs

or using the existance of the list monad:

dupli xs = xs >>= (\x -> [x,x])

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"

Solution:

repli :: [a] -> Int -> [a]
repli as n = concatMap (replicate n) as

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> drop = "abcdefghik" 3
"abdeghk"

Solution:

drop xs n = drops xs (n-1) n
drops [] _ _ = []
drops (x:xs) 0 max = drops xs (max-1) max
drops (x:xs) (n+1) max = x:drops xs n max

Here, drops is a helper-function to drop. In drops, there is an index n that counts from max-1 down to 0, and removes the head element each time it hits 0.

Note that drop is one of the standard Haskell functions, so redefining it is generally not a good idea.

or using zip:

drop n = map snd . filter ((n/=) . fst) . zip (cycle [1..n])

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")

Solution using take and drop:

split xs n = (take n xs, drop n xs)

Note that this function, with the parameters in the other order, exists as splitAt.


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 i'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

Solution:

slice xs (i+1) k = take (k-i) $ drop i xs

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"

Solution:

rotate [] _ = []
rotate l 0 = l
rotate (x:xs) (n+1) = rotate (xs ++ [x]) n
rotate l n = rotate l (length l + n)

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.


Problem 20

Remove the K'th element from a list.

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

Example in Haskell:
*Main> removeAt 1 ['a','b','c','d']
"acd"

Solution:

removeAt k xs = take k xs ++ drop (k+1) xs

Simply use the take and drop functions from the Prelude to take k elements from the start of xs and prepend to the list of elements k+1 to the end. Note that the Lisp code treats 1 as the first element in the list, and it appends NIL elements to the end of the list if k is greater than the list length.