Difference between revisions of "99 questions/1 to 10"

From HaskellWiki
Jump to navigation Jump to search
m (Fixed definition of equivalent definition using concatMap for the Elem case)
(Updated problems 2-7 to use the new format.)
Line 38: Line 38:
   
 
(*) Find the last but one box of a list.
 
(*) Find the last but one box of a list.
  +
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (my-but-last '(a b c d))
 
* (my-but-last '(a b c d))
 
(C D)
 
(C D)
 
</pre>
 
</pre>
   
  +
Example in Haskell:
This can be done by dropping all but the last two elements of a list:
 
  +
  +
<haskell>
  +
Prelude> myButLast [1,2,3,4]
  +
[3,4]
  +
Prelude> myButLast ['a'..'z']
  +
"yz"
  +
</haskell>
  +
  +
Solution:
   
 
<haskell>
 
<haskell>
Line 50: Line 61:
 
myButLast list = drop ((length list) - 2) list
 
myButLast list = drop ((length list) - 2) list
 
</haskell>
 
</haskell>
  +
  +
This simply drops all the but last two elements of a list.
   
 
== Problem 3 ==
 
== Problem 3 ==
   
(*) Find the K'th element of a list.
+
(*) Find the K'th element of a list. The first element in the list is number 1.
  +
The first element in the list is number 1.
 
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (element-at '(a b c d e) 3)
 
* (element-at '(a b c d e) 3)
 
C
 
C
 
</pre>
 
</pre>
  +
  +
Example in Haskell:
  +
  +
<haskell>
  +
Prelude> elementAt [1,2,3] 2
  +
2
  +
Prelude> elementAt "haskell" 5
  +
'e'
  +
</haskell>
  +
  +
Solution:
   
 
This is (almost) the infix operator !! in Prelude, which is defined as:
 
This is (almost) the infix operator !! in Prelude, which is defined as:
Line 80: Line 105:
 
(*) Find the number of elements of a list.
 
(*) Find the number of elements of a list.
   
  +
Example in Haskell:
This is "length" in Prelude, which is defined as:
 
  +
  +
<haskell>
  +
Prelude> length [123, 456, 789]
  +
3
  +
Prelude> length "Hello, world!"
  +
13
  +
</haskell>
  +
  +
Solution:
   
 
<haskell>
 
<haskell>
Line 87: Line 121:
 
length (_:l) = 1 + length l
 
length (_:l) = 1 + length l
 
</haskell>
 
</haskell>
  +
  +
This function is defined in Prelude.
   
 
== Problem 5 ==
 
== Problem 5 ==
Line 92: Line 128:
 
(*) Reverse a list.
 
(*) Reverse a list.
   
  +
Example in Haskell:
This is "reverse" in Prelude, which is defined as:
 
  +
  +
<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]
  +
</haskell>
  +
  +
Solution: (defined in Prelude)
   
 
<haskell>
 
<haskell>
Line 111: Line 156:
 
(*) Find out whether a list is a palindrome. A palindrome can be read forward or backward; e.g. (x a m a x).
 
(*) 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:
This is trivial, because we can use reverse:
 
  +
  +
<haskell>
  +
*Main> isPalindrome [1,2,3]
  +
False
  +
*Main> isPalindrome "madamimadam"
  +
True
  +
*Main> isPalindrome [1,2,4,8,16,8,4,2,1]
  +
True
  +
</haskell>
  +
  +
Solution:
   
 
<haskell>
 
<haskell>
Line 124: Line 180:
 
Transform a list, possibly holding lists as elements into a `flat' list by replacing each list with its elements (recursively).
 
Transform a list, possibly holding lists as elements into a `flat' list by replacing each list with its elements (recursively).
   
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (my-flatten '(a (b (c d) e)))
 
* (my-flatten '(a (b (c d) e)))
 
(A B C D E)
 
(A B C D E)
 
</pre>
 
</pre>
   
  +
Example in Haskell:
This is tricky, because lists in Haskell are homogeneous. [1, [2, [3, 4], 5]]
 
is a type error. We have to devise some way of represent a list that may (or
 
may not) be nested:
 
   
 
<haskell>
 
<haskell>
data NestedList a = Elem a | List [NestedList a]
 
 
flatten :: NestedList a -> [a]
 
flatten (Elem x) = [x]
 
flatten (List []) = []
 
flatten (List (x:xs)) = flatten x ++ flatten (List xs)
 
</haskell>
 
 
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]). Let's try it out in ghci:
 
 
<pre>
 
 
*Main> flatten (Elem 5)
 
*Main> flatten (Elem 5)
 
[5]
 
[5]
Line 153: Line 196:
 
*Main> flatten (List [])
 
*Main> flatten (List [])
 
[]
 
[]
</pre>
+
</haskell>
  +
  +
Solution:
   
An equivalent definition for flatten is
 
 
<haskell>
 
<haskell>
  +
data NestedList a = Elem a | List [NestedList a]
  +
  +
flatten :: NestedList a -> [a]
 
flatten (Elem x) = [x]
 
flatten (Elem x) = [x]
 
flatten (List x) = concatMap flatten x
 
flatten (List x) = concatMap flatten x
 
</haskell>
 
</haskell>
  +
  +
We have to defined 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 ==
 
== Problem 8 ==

Revision as of 02:30, 13 December 2006


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 1

(*) Find the last box of a list.

Example:

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

Example in Haskell:

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

Solution:

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

This function is defined in Prelude.

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.

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> length [123, 456, 789]
3
Prelude> length "Hello, world!"
13

Solution:

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

This function is defined 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]

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 defined 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

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:

Solution:

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

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

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