Difference between revisions of "99 questions/21 to 28"

From HaskellWiki
Jump to navigation Jump to search
m (link to originals)
m
Line 1: Line 1:
[[99_Haskell_exercises|Back to 99 Haskell exercises]]
 
 
 
__NOTOC__
 
__NOTOC__
   
These are Haskell translations of [http://www.ic.unicamp.br/~meidanis/courses/mc336/2006s2/funcional/L-99_Ninety-Nine_Lisp_Problems.html Ninety Nine Lisp Problems],
+
This is part of [[H-99:_Ninety-Nine_Haskell_Problems|Ninety-Nine Haskell Problems]], based on [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/ Ninety-Nine Prolog Problems] and [http://www.ic.unicamp.br/~meidanis/courses/mc336/2006s2/funcional/L-99_Ninety-Nine_Lisp_Problems.html Ninety-Nine Lisp Problems].
which are themselves translations of [http://www.hta-bi.bfh.ch/~hew/informatik3/prolog/p-99/ Ninety-Nine Prolog 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.
 
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.

Revision as of 00:57, 15 December 2006


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

or

range = enumFromTo

or

range x y = take (y-x+1) $ iterate (+1) x

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

Extract a given number of randomly selected elements from a list.

Example:
* (rnd-select '(a b c d e f g h) 3)
(E D A)

Example in Haskell:
Prelude System.Random>rnd_select "abcdefgh" 3
Prelude System.Random>"eda"

Solution:

import System.Random

rnd_select :: [a]->Int->IO [a]
rnd_select [] _ = return []
rnd_select l  n 
    | n<0 = error "N must be greater than zero."
    | otherwise = do pos<-sequence$replicate n$getStdRandom$randomR (0,(length l)-1)
                     return [l!!p | p<-pos]

In order to use getStdRandom and randomR here, we need import module System.Random.

or using sequence all the way:

rnd_select xs n 
    | n < 0     = error "N must be greater than zero."
    | otherwise = sequence $ replicate n rand
        where rand = do r <- randomRIO (0,(length xs) - 1)
                        return (xs!!r)

Alternative Solution:

The original Lisp problem suggested we use our solution from problem 20. I believe that each item from the list should only appear once, whereas the above solution can reuse items.

Therefore here is an alternative which uses the "removeAt" function from problem 20:

rnd_select :: RandomGen g => [a] -> Int -> g -> ([a], g)
rnd_select _ 0 gen = ([], gen)
rnd_select [] _ gen = ([], gen)
rnd_select l count gen
   | count == (length l) = (l, gen)
   | otherwise           =  rnd_select (removeAt k l) count gen'
                            where (k, gen') = randomR (0, length l) gen

rnd_selectIO :: [a] -> Int -> IO [a]
rnd_selectIO l count = getStdRandom $ rnd_select l count

If the number of items we want is the same as the number of items in the list, then we just return the list. Otherwise we remove a random item from the list and then recurse.

Problem 24

Lotto: Draw N different random numbers from the set 1..M.

Example:
* (rnd-select 6 49)
(23 1 17 33 21 37)

Example in Haskell:
Prelude System.Random>diff_select 6 49
Prelude System.Random>[23,1,17,33,21,37]

Solution:

import System.Random
diff_select :: Int -> Int -> IO [Int]
diff_select n to = diff_select' n [1..to]

diff_select' 0 _  = return []
diff_select' _ [] = error "too few elements to choose from"
diff_select' n xs = do r <- randomRIO (0,(length xs)-1)
                       let remaining = take r xs ++ drop (r+1) xs
                       rest <- diff_select' (n-1) remaining
                       return ((xs!!r) : rest)

The random numbers have to be distinct!

In order to use getStdRandom and randomR here, we need import module System.Random.

Problem 25

Generate a random permutation of the elements of a list.

Example:
* (rnd-permu '(a b c d e f))
(B A D C E F)


Example in Haskell:
Prelude>rnd_permu "abcdef"
Prelude>"badcef"

Solution:

rnd_permu xs = diff_select' (length xs) xs

Uses the solution for the previous problem. Choosing N distinct elements from a list of length N will yield a permutation.

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

Sorting a list of lists according to length of sublists

a) We suppose that a list contains elements that are lists themselves. The objective is to sort the elements of this list according to their length. E.g. short lists first, longer lists later, or vice versa.

Example:
* (lsort '((a b c) (d e) (f g h) (d e) (i j k l) (m n) (o)))
((O) (D E) (D E) (M N) (A B C) (F G H) (I J K L))

Example in Haskell:
Prelude>lsort ["abc","de","fgh","de","ijkl","mn","o"]
Prelude>["o","de","de","mn","abc","fgh","ijkl"]

Solution:

import List
lsort :: [[a]]->[[a]]
lsort = sortBy (\x y->compare (length x) (length y))

This function also works for empty list. Import List to use sortBy.

b) Again, we suppose that a list contains elements that are lists themselves. But this time the objective is to sort the elements of this list according to their length frequency; i.e., in the default, where sorting is done ascendingly, lists with rare lengths are placed first, others with a more frequent length come later.

Example:
* (lfsort '((a b c) (d e) (f g h) (d e) (i j k l) (m n) (o)))
((i j k l) (o) (a b c) (f g h) (d e) (d e) (m n))

Example in Haskell:
lfsort ["abc", "de", "fgh", "de", "ijkl", "mn", "o"]
["ijkl","o","abc","fgh","de","de","mn"]

Solution:

import List
comparing p x y = compare (p x) (p y)
lfsort lists = sortBy (comparing frequency) lists where
    lengths = map length lists
    frequency list = length $ filter (== length list) lengths

What we need is a function that takes a sublist and counts the number of other sublists with the same length. To do this, we first construct a list containing the lengths of all the sublists (called lengths above). Then the function frequency can just count the number of times that the current sublist's length occurs in lengths.