Difference between revisions of "99 questions/46 to 50"

From HaskellWiki
Jump to navigation Jump to search
m
(moved solutions to subpages of 99 questions/Solutions)
Line 15: Line 15:
 
Now, write a predicate table/3 which prints the truth table of a given logical expression in two variables.
 
Now, write a predicate table/3 which prints the truth table of a given logical expression in two variables.
   
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
(table A B (and A (or A B)))
 
(table A B (and A (or A B)))
 
true true true
 
true true true
Line 22: Line 23:
 
fail true fail
 
fail true fail
 
fail fail fail
 
fail fail fail
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
> table2 (\a b -> (and' a (or' a b))
 
> table2 (\a b -> (and' a (or' a b))
 
True True True
 
True True True
Line 29: Line 33:
 
False True False
 
False True False
 
False False False
 
False False False
</pre>
 
 
Solution:
 
<haskell>
 
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' False False = False
 
or' _ _ = True
 
 
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 = mapM_ putStrLn [show a ++ " " ++ show b ++ " " ++ show (f a b)
 
| a <- [True, False], b <- [True, False]]
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/46 | Solutions]]
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 ==
 
== Problem 47 ==
Line 71: Line 43:
   
 
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.
 
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:
   
 
<pre>
 
<pre>
Example:
 
 
* (table A B (A and (A or not B)))
 
* (table A B (A and (A or not B)))
 
true true true
 
true true true
Line 79: Line 52:
 
fail true fail
 
fail true fail
 
fail fail fail
 
fail fail fail
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
> table2 (\a b -> a `and'` (a `or'` not b))
 
> table2 (\a b -> a `and'` (a `or'` not b))
 
True True True
 
True True True
Line 86: Line 62:
 
False True False
 
False True False
 
False False False
 
False False False
</pre>
 
 
Solution:
 
<haskell>
 
-- functions as in solution 46
 
infixl 4 `or'`
 
infixl 6 `and'`
 
-- "not" has fixity 9 by default
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/47 | Solutions]]
Java operator precedence (descending) as far as I could fathom it:
 
<pre>
 
logical not
 
equality
 
and
 
xor
 
or
 
</pre>
 
 
Using "not" as a non-operator is a little evil, but then again these problems were designed for languages other than haskell :)
 
 
 
 
== Problem 48 ==
 
== Problem 48 ==
Line 113: Line 72:
 
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.
 
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.
   
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (table (A,B,C) (A and (B or C) equ A and B or A and C))
 
* (table (A,B,C) (A and (B or C) equ A and B or A and C))
 
true true true true
 
true true true true
Line 124: Line 84:
 
fail fail true true
 
fail fail true true
 
fail fail fail true
 
fail fail fail true
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
  +
<haskell>
 
> tablen 3 (\[a,b,c] -> a `and'` (b `or'` c) `equ'` a `and'` b `or'` a `and'` c)
 
> tablen 3 (\[a,b,c] -> a `and'` (b `or'` c) `equ'` a `and'` b `or'` a `and'` c)
 
True True True True
 
True True True True
Line 135: Line 98:
 
False False True True
 
False False True True
 
False False False True
 
False False False True
</pre>
+
</haskell>
   
  +
[[99 questions/Solutions/48 | Solutions]]
Solution:
 
<haskell>
 
import Control.Monad (replicateM)
 
   
-- 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 :(
 
 
tablen :: Int -> ([Bool] -> Bool) -> IO ()
 
tablen n f = mapM_ putStrLn [toStr a ++ " => " ++ show (f a) | a <- args n]
 
where args n = replicateM n [True, False]
 
toStr = unwords . map show
 
</haskell>
 
 
 
 
== Problem 49 ==
 
== Problem 49 ==
Line 160: Line 108:
   
 
An n-bit Gray code is a sequence of n-bit strings constructed according to certain rules. For example,
 
An n-bit Gray code is a sequence of n-bit strings constructed according to certain rules. For example,
  +
 
<pre>
 
<pre>
 
n = 1: C(1) = ['0','1'].
 
n = 1: C(1) = ['0','1'].
Line 168: Line 117:
 
Find out the construction rules and write a predicate with the following specification:
 
Find out the construction rules and write a predicate with the following specification:
   
  +
<pre>
 
% gray(N,C) :- C is the N-bit Gray code
 
% gray(N,C) :- C is the N-bit Gray code
  +
</pre>
   
 
Can you apply the method of "result caching" in order to make the predicate more efficient, when it is to be used repeatedly?
 
Can you apply the method of "result caching" in order to make the predicate more efficient, when it is to be used repeatedly?
   
<pre>
 
 
Example in Haskell:
 
Example in Haskell:
P49> gray 3
 
["000","001","011","010","110","111","101","100"]
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
P49> gray 3
gray :: Int -> [String]
 
  +
["000","001","011","010","110","111","101","100"]
gray 0 = [""]
 
gray n = let xs = gray (n-1) in map ('0':) xs ++ map ('1':) (reverse xs)
 
 
</haskell>
 
</haskell>
   
  +
[[99 questions/Solutions/49 | Solutions]]
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 [http://en.wikipedia.org/wiki/Gray_code Wikipedia article] seems to approve this.)
 
 
 
 
== Problem 50 ==
 
== Problem 50 ==
Line 194: Line 139:
 
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:
 
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:
   
  +
<pre>
 
% 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
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
<pre>
+
<haskell>
 
*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")]
 
[('a',"0"),('b',"101"),('c',"100"),('d',"111"),('e',"1101"),('f',"1100")]
</pre>
 
 
Solution:
 
<haskell>
 
import Data.List
 
import Data.Ord (comparing)
 
 
data HTree a = Leaf a | Branch (HTree a) (HTree a)
 
deriving Show
 
 
huffman :: (Ord a, Ord w, Num w) => [(a,w)] -> [(a,[Char])]
 
huffman freq = sortBy (comparing fst) $ serialize $
 
htree $ sortBy (comparing fst) $ [(w, Leaf x) | (x,w) <- freq]
 
where htree [(_, t)] = t
 
htree ((w1,t1):(w2,t2):wts) =
 
htree $ insertBy (comparing fst) (w1 + w2, Branch t1 t2) wts
 
serialize (Branch l r) =
 
[(x, '0':code) | (x, code) <- serialize l] ++
 
[(x, '1':code) | (x, code) <- serialize r]
 
serialize (Leaf x) = [(x, "")]
 
 
</haskell>
 
</haskell>
The argument to <tt>htree</tt> is a list of (weight, tree) pairs, in order of increasing weight.
 
The implementation could be made more efficient by using a priority queue instead of an ordered list.
 
   
  +
[[99 questions/Solutions/50 | Solutions]]
Or, a solution that does not use trees:
 
<haskell>
 
import List
 
-- tupleUpdate - a function to record the Huffman codes; add string
 
-- "1" or "0" to element 'c' of tuple array ta
 
-- let ta = [('a',"0"),('b',"1")]
 
-- tupleUpdate ta 'c' "1" => [('c',"1"),('a',"0"),('b',"1")]
 
tupleUpdate :: [(Char,[Char])]->Char->String ->[(Char,[Char])]
 
tupleUpdate ta el val
 
| ((dropWhile(\x -> (fst x)/= el) ta)==[])= (el,val):ta
 
| otherwise = (takeWhile (\x -> (fst x)/=el) ta) ++ ((fst(head ha),val ++ snd(head ha)) : (tail (dropWhile (\x -> (fst x)/=el) ta)))
 
where ha = [(xx,yy)|(xx,yy) <- ta,xx ==el]
 
   
-- tupleUpdater - wrapper for tupleUpdate, use a list decomposition "for loop"
 
-- let ta = [('a',"0"),('b',"1")]
 
-- tupleUpdater ta "fe" "1" => [('e',"1"),('f',"1"),('a',"0"),('b',"1")]
 
tupleUpdater :: [(Char,[Char])]->String->String ->[(Char,[Char])]
 
tupleUpdater a (x:xs) c = tupleUpdater (tupleUpdate a x c) xs c
 
tupleUpdater a [] c = a
 
 
-- huffer - recursively run the encoding algorithm and record the left/right
 
-- codes as they are discovered in argument hc, which starts as []
 
-- let ha =[(45,"a"),(13,"b"),(12,"c"),(16,"d"),(9,"e"),(5,"f")]
 
-- huffer ha [] => ([(100,"acbfed")],[('a',"0"),('b',"101"),('c',"100"),('d',"111"),('e',"1101"),('f',"1100")])
 
huffer :: [(Integer,String)] -> [(Char,[Char])]-> ([(Integer,String)],[(Char,[Char])])
 
huffer ha hc
 
| ((length ha)==1)=(ha,sort hc)
 
| otherwise = huffer ((num,str): tail(tail(has)) ) hc2
 
where num = fst (head has) + fst (head (tail has))
 
left = snd (head has)
 
rght = snd (head (tail has))
 
str = left ++ rght
 
has = sort ha
 
hc2 = tupleUpdater (tupleUpdater hc rght "1") left "0"
 
 
-- huffman - wrapper for huffer to convert the input to a format huffer likes
 
-- and extract the output to match the problem specification
 
huffman :: [(Char,Integer)] -> [(Char,[Char])]
 
huffman h = snd(huffer (zip (map snd h) (map (:[]) (map fst h))) [])
 
 
</haskell>
 
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Revision as of 21:30, 13 July 2010


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

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

Solutions


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

Solutions

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:

> tablen 3 (\[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

Solutions


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

Solutions


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

Solutions