99 questions/46 to 50: Difference between revisions
RossPaterson (talk | contribs) m (add stars) |
RossPaterson (talk | contribs) (tighten up Huffman) |
||
Line 198: | Line 198: | ||
% huffman(Fs,Hs) :- Hs is the Huffman code table for the frequency table Fs | % huffman(Fs,Hs) :- Hs is the Huffman code table for the frequency table Fs | ||
Example in Haskell: | |||
<pre> | <pre> | ||
*Exercises> huffman [('a',45),('b',13),('c',12),('d',16),('e',9),('f',5)] | *Exercises> huffman [('a',45),('b',13),('c',12),('d',16),('e',9),('f',5)] | ||
[(" | [('a',"0"),('b',"101"),('c',"100"),('d',"111"),('e',"1101"),('f',"1100")] | ||
</pre> | </pre> | ||
Solution: | Solution: | ||
<haskell> | <haskell> | ||
data | import Data.List | ||
data HTree = Leaf Char | Branch HTree HTree | |||
deriving Show | |||
huffman | huffman :: (Ord a, Num a) => [(Char,a)] -> [(Char,[Char])] | ||
huffman freq = sortBy cmpFst $ serialize $ | |||
htree $ sortBy cmpFst $ [(w, Leaf c) | (c,w) <- freq] | |||
where htree [(_, t)] = t | |||
htree ((wx,tx):(wy,ty):rest) = | |||
htree $ insertBy cmpFst (wx + wy, Branch tx ty) rest | |||
cmpFst x y = compare (fst x) (fst y) | |||
serialize (Branch l r) = | |||
[(c, '0':code) | (c, code) <- serialize l] ++ | |||
[(c, '1':code) | (c, code) <- serialize r] | |||
serialize (Leaf c) = [(c, "")] | |||
</haskell> | </haskell> | ||
[[Category:Tutorials]] | [[Category:Tutorials]] |
Revision as of 18:15, 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.
Logic and Codes
Problem 46
(**) Define predicates and/2, or/2, nand/2, nor/2, xor/2, impl/2 and equ/2 (for logical equivalence) which succeed or fail according to the result of their respective operations; e.g. and(A,B) will succeed, if and only if both A and B succeed.
A logical expression in two variables can then be written as in the following example: and(or(A,B),nand(A,B)).
Now, write a predicate table/3 which prints the truth table of a given logical expression in two variables.
Example: (table A B (and A (or A B))) true true true true fail true fail true fail fail fail fail Example in Haskell: > table2 (\a b -> (and' a (or' a b)) True True True True False True False True False False False False
Solution:
not' :: Bool -> Bool
not' True = False
not' False = True
and',or',nor',nand',xor',impl',equ' :: Bool -> Bool -> Bool
and' True True = True
and' _ _ = False
or' True _ = True
or' _ True = True
or' _ _ = False
nor' a b = not' $ or' a b
nand' a b = not' $ and' a b
xor' True False = True
xor' False True = True
xor' _ _ = False
impl' a b = (not' a) `or'` b
equ' True True = True
equ' False False = True
equ' _ _ = False
table2 :: (Bool -> Bool -> Bool) -> IO ()
table2 f = putStrLn . unlines $ [show a ++ " " ++ show b ++ " " ++ show (f a b)
| a <- [True, False], b <- [True, False]]
The implementations of the logic functions are quite verbose and can be shortened in places (like "equ' = (==)").
The table function in Lisp supposedly uses Lisp's symbol handling to substitute variables on the fly in the expression. I chose passing a binary function instead because parsing an expression would be more verbose in haskell than it is in Lisp. Template Haskell could also be used :)
Problem 47
(*) Truth tables for logical expressions (2).
Continue problem P46 by defining and/2, or/2, etc as being operators. This allows to write the logical expression in the more natural way, as in the example: A and (A or not B). Define operator precedence as usual; i.e. as in Java.
Example: * (table A B (A and (A or not B))) true true true true fail true fail true fail fail fail fail Example in Haskell: > table2 (\a b -> a `and'` (a `or'` not b)) True True True True False True False True False False False False
Solution:
-- functions as in solution 46
infixl 4 `or'`
infixl 6 `and'`
-- "not" has fixity 9 by default
Java operator precedence (descending) as far as I could fathom it:
logical not equality and xor or
Using "not" as a non-operator is a little evil, but then again these problems were designed for languages other than haskell :)
Problem 48
(**) Truth tables for logical expressions (3).
Generalize problem P47 in such a way that the logical expression may contain any number of logical variables. Define table/2 in a way that table(List,Expr) prints the truth table for the expression Expr, which contains the logical variables enumerated in List.
Example: * (table (A,B,C) (A and (B or C) equ A and B or A and C)) true true true true true true fail true true fail true true true fail fail true fail true true true fail true fail true fail fail true true fail fail fail true Example in Haskell: > table3 (\a b c -> a `and'` (b `or'` c) `equ'` a `and'` b `or'` a `and'` c) True True True True True True False True True False True True True False False True False True True True False True False True False False True True False False False True
Solution:
-- functions as in solution 46
infixl 4 `or'`
infixl 4 `nor'`
infixl 5 `xor'`
infixl 6 `and'`
infixl 6 `nand'`
infixl 3 `equ'` -- was 7, changing it to 3 got me the same results as in the original question :(
table3 :: (Bool -> Bool -> Bool -> Bool) -> IO ()
table3 f = putStrLn . unlines $ [show a ++ " " ++ show b ++ " " ++ show c ++ " " ++ show (f a b c)
| a <- [True, False], b <- [True, False], c <- [True, False]]
Using individual table functions for different numbers of variables is even more ugly, but anything else would be a bit of a pain in haskell AFAIK.
Problem 49
(**) Gray codes.
An n-bit Gray code is a sequence of n-bit strings constructed according to certain rules. For example,
n = 1: C(1) = ['0','1']. n = 2: C(2) = ['00','01','11','10']. n = 3: C(3) = ['000','001','011','010',´110´,´111´,´101´,´100´].
Find out the construction rules and write a predicate with the following specification:
% gray(N,C) :- C is the N-bit Gray code
Can you apply the method of "result caching" in order to make the predicate more efficient, when it is to be used repeatedly?
Example in Haskell: P49> gray 3 ["000","001","011","010","110","111","101","100"]
Solution:
gray :: Int -> [String]
gray 0 = [""]
gray n = let xs = gray (n-1) in map ('0':) xs ++ map ('1':) (reverse xs)
It seems that the Gray code can be recursively defined in the way that for determining the gray code of n we take the Gray code of n-1, prepend a 0 to each word, take the Gray code for n-1 again, reverse it and prepend a 1 to each word. At last we have to append these two lists. (The Wikipedia article seems to approve this.)
Problem 50
(***) Huffman codes.
We suppose a set of symbols with their frequencies, given as a list of fr(S,F) terms. Example: [fr(a,45),fr(b,13),fr(c,12),fr(d,16),fr(e,9),fr(f,5)]. Our objective is to construct a list hc(S,C) terms, where C is the Huffman code word for the symbol S. In our example, the result could be Hs = [hc(a,'0'), hc(b,'101'), hc(c,'100'), hc(d,'111'), hc(e,'1101'), hc(f,'1100')] [hc(a,'01'),...etc.]. The task shall be performed by the predicate huffman/2 defined as follows:
% huffman(Fs,Hs) :- Hs is the Huffman code table for the frequency table Fs
Example in Haskell:
*Exercises> huffman [('a',45),('b',13),('c',12),('d',16),('e',9),('f',5)] [('a',"0"),('b',"101"),('c',"100"),('d',"111"),('e',"1101"),('f',"1100")]
Solution:
import Data.List
data HTree = Leaf Char | Branch HTree HTree
deriving Show
huffman :: (Ord a, Num a) => [(Char,a)] -> [(Char,[Char])]
huffman freq = sortBy cmpFst $ serialize $
htree $ sortBy cmpFst $ [(w, Leaf c) | (c,w) <- freq]
where htree [(_, t)] = t
htree ((wx,tx):(wy,ty):rest) =
htree $ insertBy cmpFst (wx + wy, Branch tx ty) rest
cmpFst x y = compare (fst x) (fst y)
serialize (Branch l r) =
[(c, '0':code) | (c, code) <- serialize l] ++
[(c, '1':code) | (c, code) <- serialize r]
serialize (Leaf c) = [(c, "")]