99 questions/1 to 10

From HaskellWiki
< 99 questions
Revision as of 13:06, 12 September 2007 by Chrycheng (talk | contribs) (Revised problem 4 example to differentiate the required solution from the Prelude function.)
Jump to navigation Jump to search


This is part of Ninety-Nine Haskell Problems, based on Ninety-Nine Prolog Problems and 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 1

(*) Find the last box of a list.

Example:

* (my-last '(a b c d))
(D)

Example in Haskell:

Prelude> myLast [1,2,3,4]
[4]
Prelude> myLast ['x','y','z']
"z"

Solution:

myLast :: [a] -> [a]
myLast [x] = [x]
myLast (_:xs) = myLast xs

Haskell also provides the function last.

Problem 2

(*) Find the last but one box of a list.

Example:

* (my-but-last '(a b c d))
(C D)

Example in Haskell:

Prelude> myButLast [1,2,3,4]
[3,4]
Prelude> myButLast ['a'..'z']
"yz"

Solution:

myButLast :: [a] -> [a]
myButLast list = drop ((length list) - 2) list

This simply drops all the but last two elements of a list.

Some other options:

myButLast = reverse . take 2 . reverse

or

myButLast list = snd $ splitAt (length list - 2) list

or

myButLast = last . liftM2 (zipWith const) tails (drop 1)

or

myButLast [a, b] = [a, b]
myButLast (_ : xs) = myButLast xs

(I'm very new to Haskell but this last one definitely seems to work -- bakert.)

Remark: The Lisp solution is actually wrong, it should not be the last two elements; a correct Haskell solution is:

myButLast = last . init
Prelude> myButLast ['a'..'z']
'y'

See also the solution to problem 2 in the Prolog list.

Problem 3

(*) Find the K'th element of a list. The first element in the list is number 1.

Example:

* (element-at '(a b c d e) 3)
C

Example in Haskell:

Prelude> elementAt [1,2,3] 2
2
Prelude> elementAt "haskell" 5
'e'

Solution:

This is (almost) the infix operator !! in Prelude, which is defined as:

(!!)                :: [a] -> Int -> a
(x:_)  !! 0         =  x
(_:xs) !! n         =  xs !! (n-1)

Except this doesn't quite work, because !! is zero-indexed, and element-at should be one-indexed. So:

elementAt :: [a] -> Int -> a
elementAt list i = list !! (i-1)

Problem 4

(*) Find the number of elements of a list.

Example in Haskell:

Prelude> myLength [123, 456, 789]
3
Prelude> myLength "Hello, world!"
13

Solution:

myLength           :: [a] -> Int
myLength []        =  0
myLength (_:l)     =  1 + myLength l

This is length in Prelude.

Problem 5

(*) Reverse a list.

Example in Haskell:

Prelude> reverse "A man, a plan, a canal, panama!"
"!amanap ,lanac a ,nalp a ,nam A"
Prelude> reverse [1,2,3,4]
[4,3,2,1]

Solution: (defined in Prelude)

reverse          :: [a] -> [a]
reverse          =  foldl (flip (:)) []

The standard definition is concise, but not very readable. Another way to define reverse is:

reverse :: [a] -> [a]
reverse [] = []
reverse (x:xs) = reverse xs ++ [x]

However this definition is more wasteful than the one in Prelude as it repeatedly reconses the result as it is accumulated. The following variation avoids that, and thus computationally closer to the Prelude version.

reverse :: [a] -> [a]
reverse list = reverse' list []
  where
    reverse' [] reversed     = reversed
    reverse' (x:xs) reversed = reverse' xs (x:reversed)

Problem 6

(*) Find out whether a list is a palindrome. A palindrome can be read forward or backward; e.g. (x a m a x).

Example in Haskell:

*Main> isPalindrome [1,2,3]
False
*Main> isPalindrome "madamimadam"
True
*Main> isPalindrome [1,2,4,8,16,8,4,2,1]
True

Solution:

isPalindrome :: (Eq a) => [a] -> Bool
isPalindrome xs = xs == (reverse xs)

Problem 7

(**) Flatten a nested list structure.

Transform a list, possibly holding lists as elements into a `flat' list by replacing each list with its elements (recursively).

Example:

* (my-flatten '(a (b (c d) e)))
(A B C D E)

Example in Haskell:

*Main> flatten (Elem 5)
[5]
*Main> flatten (List [Elem 1, List [Elem 2, List [Elem 3, Elem 4], Elem 5]])
[1,2,3,4,5]
*Main> flatten (List [])
[]

Solution:

data NestedList a = Elem a | List [NestedList a]

flatten :: NestedList a -> [a]
flatten (Elem x) = [x]
flatten (List x) = concatMap flatten x

We have to define a new data type, because lists in Haskell are homogeneous. [1, [2, [3, 4], 5]] is a type error. Therefore, we must have a way of representing a list that may (or may not) be nested.

Our NestedList datatype is either a single element of some type (Elem a), or a list of NestedLists of the same type. (List [NestedList a]).

Problem 8

(**) Eliminate consecutive duplicates of list elements.

If a list contains repeated elements they should be replaced with a single copy of the element. The order of the elements should not be changed.

Example:
* (compress '(a a a a b c c a a d e e e e))
(A B C A D E)

Example in Haskell:
*Main> compress ['a','a','a','a','b','c','c','a','a','d','e','e','e','e']
['a','b','c','a','d','e']

Solution:

compress :: Eq a => [a] -> [a]
compress = map head . group

We simply group equal values together (group), then take the head of each. Note that (with GHC) we must give an explicit type to compress otherwise we get:

Ambiguous type variable `a' in the constraint:
      `Eq a'
	arising from use of `group'	
    Possible cause: the monomorphism restriction applied to the following:
      compress :: [a] -> [a]
    Probable fix: give these definition(s) an explicit type signature
		  or use -fno-monomorphism-restriction

We can circumvent the monomorphism restriction by writing compress this way (See: section 4.5.4 of the report):

compress xs = map head $ group xs

An alternative solution is

compress [] = []
compress [a] = [a]
compress (x : y : xs) = (if x == y then [] else [x]) ++ compress (y : xs)

Problem 9

(**) Pack consecutive duplicates of list elements into sublists. If a list contains repeated elements they should be placed in separate sublists.

Example:
* (pack '(a a a a b c c a a d e e e e))
((A A A A) (B) (C C) (A A) (D) (E E E E))
<example in lisp>

Example in Haskell:
*Main> pack ['a', 'a', 'a', 'a', 'b', 'c', 'c', 'a', 'a', 'd', 'e', 'e', 'e', 'e']
["aaaa","b","cc","aa","d","eeee"]

Solution:

pack (x:xs) = let (first,rest) = span (==x) xs
               in (x:first) : pack rest
pack [] = []

'group' is also in the Prelude, here's an implementation using 'span'.

Problem 10

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

Example:

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

Example in Haskell:

encode "aaaabccaadeeee"
[(4,'a'),(1,'b'),(2,'c'),(2,'a'),(1,'d'),(4,'e')]

Solution:

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:

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