99 questions/21 to 28

From HaskellWiki
< 99 questions
Revision as of 15:36, 12 December 2006 by RossPaterson (talk | contribs) (there are no problems 29 or 30)
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 21

Insert an element at a given position into a list.

Example:
* (insert-at 'alfa '(a b c d) 2)
(A ALFA B C D)
Example in Haskell:
P21> insertAt 'X' "abcd" 2
"aXbcd"

Solution:

insertAt :: a -> [a] -> Int -> [a]
insertAt x xs (n+1) = let (ys,zs) = split xs n in ys++x:zs

or

insertAt :: a -> [a] -> Int -> [a]
insertAt x ys     1 = x:ys
insertAt x (y:ys) n = y:insertAt x ys (n-1)

There are two possible simple solutions. First we can use split from problem 17 (or even splitAt from the Prelude) to split the list and insert the element. Second we can define a recursive solution on our own.

Problem 22

Create a list containing all integers within a given range.

Example:
* (range 4 9)
(4 5 6 7 8 9)

Example in Haskell:
Prelude> [4..9]
[4,5,6,7,8,9]

Solution:

range x y = [x..y]
range = enumFromTo

Since there's already syntactic sugar for ranges, there's usually no reason to define a function like 'range' in Haskell. In fact, the syntactic sugar is implemented using the enumFromTo function, which is exactly what 'range' should be.

Problem 23

<Problem description>

Example:
<example in lisp>

Example in Haskell:
<example in Haskell>

Solution:

<solution in haskell>

<description of implementation>

Problem 24

<Problem description>

Example:
<example in lisp>

Example in Haskell:
<example in Haskell>

Solution:

<solution in haskell>

<description of implementation>

Problem 25

<Problem description>

Example:
<example in lisp>

Example in Haskell:
<example in Haskell>

Solution:

<solution in haskell>

<description of implementation>

Problem 26

(**) Generate the combinations of K distinct objects chosen from the N elements of a list In how many ways can a committee of 3 be chosen from a group of 12 people? We all know that there are C(12,3) = 220 possibilities (C(N,K) denotes the well-known binomial coefficients). For pure mathematicians, this result may be great. But we want to really generate all the possibilities in a list.

Example:
* (combinations 3 '(a b c d e f))
((A B C) (A B D) (A B E) ... )

Example in Haskell:
> combinations 3 "abcdef"
["abc","abd","abe",...]

Solution:

-- Import the 'tails' function
--   > tails [0,1,2,3]
--   [[0,1,2,3],[1,2,3],[2,3],[3],[]]
import Data.List (tails)

-- The implementation first checks if there's no more elements to select,
-- if so, there's only one possible combination, the empty one,
-- otherwise we need to select 'n' elements. Since we don't want to
-- select an element twice, and we want to select elements in order, to
-- avoid combinations which only differ in ordering, we skip some
-- unspecified initial elements with 'tails', and select the next element,
-- also recursively selecting the next 'n-1' element from the rest of the
-- tail, finally consing them together

-- Using list comprehensions
combinations :: Int -> [a] -> [[a]]
combinations 0 _  = [ [] ]
combinations n xs = [ y:ys | y:xs' <- tails xs
                           , ys <- combinations (n-1) xs']

-- Alternate syntax, using 'do'-notation 
combinations :: Int -> [a] -> [[a]]
combinations 0 _  = do return []
combinations n xs = do y:xs' <- tails xs
                       ys <- combinations (n-1) xs'
                       return (y:ys)

Problem 27

Group the elements of a set into disjoint subsets.

a) In how many ways can a group of 9 people work in 3 disjoint subgroups of 2, 3 and 4 persons? Write a function that generates all the possibilities and returns them in a list.

Example:
* (group3 '(aldo beat carla david evi flip gary hugo ida))
( ( (ALDO BEAT) (CARLA DAVID EVI) (FLIP GARY HUGO IDA) )
... )

b) Generalize the above predicate in a way that we can specify a list of group sizes and the predicate will return a list of groups.

Example:
* (group '(aldo beat carla david evi flip gary hugo ida) '(2 2 5))
( ( (ALDO BEAT) (CARLA DAVID) (EVI FLIP GARY HUGO IDA) )
... )

Note that we do not want permutations of the group members; i.e. ((ALDO BEAT) ...) is the same solution as ((BEAT ALDO) ...). However, we make a difference between ((ALDO BEAT) (CARLA DAVID) ...) and ((CARLA DAVID) (ALDO BEAT) ...).

You may find more about this combinatorial problem in a good book on discrete mathematics under the term "multinomial coefficients".

Example in Haskell:
<example in Haskell>

P27> group [2,3,4] ["aldo","beat","carla","david","evi","flip","gary","hugo","ida"]
[[["aldo","beat"],["carla","david","evi"],["flip","gary","hugo","ida"]],...]
(altogether 1260 solutions)

27> group [2,2,5] ["aldo","beat","carla","david","evi","flip","gary","hugo","ida"]
[[["aldo","beat"],["carla","david"],["evi","flip","gary","hugo","ida"]],...]
(altogether 756 solutions)

Solution:

combination :: Int -> [a] -> [([a],[a])]
combination 0 xs     = [([],xs)]
combination n []     = []
combination n (x:xs) = ts ++ ds
  where
    ts = [ (x:ys,zs) | (ys,zs) <- combination (n-1) xs ]
    ds = [ (ys,x:zs) | (ys,zs) <- combination  n    xs ]

group :: [Int] -> [a] -> [[[a]]]
group [] _ = [[]]
group (n:ns) xs = do
    (g,rs) <- combination n xs
    gs      <- group ns rs
    return $ g:gs

First of all we acknowledge that we need something like combination from the above problem. Actually we need more than the elements we selected, we also need the elements we did not select. Therefore we cannot use the tails function because it throws too much information away. But in general this function works like the one above. In each step of the recursion we have to decide whether we want to take the first element of the list (x:xs) in the combination (we collect the possibilities for this choice in ts) or if we don't want it in the combination (ds collects the possibilities for this case).

Now we need a function group that does the needed work. First we denote that if we don't want any group there is only one solution: a list of no groups. But if we want at least one group with n members we have to select n elements of xs into a group g and the remaining elements into rs. Afterwards we group those remaining elements, get a list of groups gs and prepend g as the first group.

And a way for those who like it shorter (but less comprehensive):

group :: [Int] -> [a] -> [[[a]]]
group [] = const [[]]
group (n:ns) = concatMap (uncurry $ (. group ns) . map . (:)) . combination n

Problem 28

<Problem description>

Example:
<example in lisp>

Example in Haskell:
<example in Haskell>

Solution:

<solution in haskell>

<description of implementation>