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

From HaskellWiki
Jump to navigation Jump to search
m (link)
m
 
(24 intermediate revisions by 11 users not shown)
Line 1: Line 1:
[[99_Haskell_exercises|Back to 99 Haskell exercises]]
 
 
 
__NOTOC__
 
__NOTOC__
   
  +
This is part of [[H-99:_Ninety-Nine_Haskell_Problems|Ninety-Nine Haskell Problems]], based on [https://prof.ti.bfh.ch/hew1/informatik3/prolog/p-99/ Ninety-Nine Prolog Problems].
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].
 
 
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 ==
 
== Logic and Codes ==
 
 
 
== Problem 46 ==
 
== Problem 46 ==
  +
<div style="border-bottom:1px solid #eee">(**) Truth tables for logical expressions. <span style="float:right"><small>[[99 questions/Solutions/46|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
 
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.
 
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.
Line 16: 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.
  +
  +
Example:
   
 
<pre>
 
<pre>
Example:
 
 
(table A B (and A (or A B)))
 
(table A B (and A (or A B)))
 
true true true
 
true true true
Line 24: Line 24:
 
fail true fail
 
fail true fail
 
fail fail fail
 
fail fail fail
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
  +
> table (\a b -> (and' a (or' a b))
 
  +
<haskell>
  +
λ> table (\a b -> (and' a (or' a b)))
 
True True True
 
True True True
 
True False True
 
True False True
 
False True False
 
False True False
 
False False False
 
False False False
</pre>
 
 
Solution:
 
<haskell>
 
and' True True = True
 
and' _ _ = False
 
 
or' True _ = True
 
or' _ True = True
 
or' _ _ = False
 
 
not' True = False
 
not' False = True
 
 
nor' = not' . or'
 
nand' = not' . and'
 
 
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
 
 
table f = putStrLn . unlines $ [show a ++ " " ++ show b ++ " " ++ show (f a b)
 
| a <- [True, False], b <- [True, False]
 
 
</haskell>
 
</haskell>
   
The implementations of the logic functions are quite verbose and can be shortened in places (like "equ' = (==)").
 
   
The table function in Lisp supposedly uses lisps 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 in Lisp
 
 
 
== Problem 47 ==
 
== Problem 47 ==
  +
<div style="border-bottom:1px solid #eee">(*) Truth tables for logical expressions (part 2). <span style="float:right"><small>[[99 questions/Solutions/47|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
Continue Problem 46 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.
<Problem description>
 
   
<pre>
 
 
Example:
 
Example:
<example in lisp>
 
   
  +
<pre>
Example in Haskell:
 
  +
* (table A B (A and (A or not B)))
<example in Haskell>
 
  +
true true true
  +
true fail true
  +
fail true fail
  +
fail fail fail
 
</pre>
 
</pre>
   
  +
Example in Haskell:
Solution:
 
  +
 
<haskell>
 
<haskell>
  +
λ> table2 (\a b -> a `and'` (a `or'` not b))
<solution in haskell>
 
  +
True True True
  +
True False True
  +
False True False
  +
False False False
 
</haskell>
 
</haskell>
   
<description of implementation>
 
 
 
 
== Problem 48 ==
 
== Problem 48 ==
  +
<div style="border-bottom:1px solid #eee">(*) Truth tables for logical expressions (part 3). <span style="float:right"><small>[[99 questions/Solutions/48|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
Generalize Problem 47 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.
<Problem description>
 
   
<pre>
 
 
Example:
 
Example:
<example in lisp>
 
   
  +
<pre>
Example in Haskell:
 
  +
* (table (A,B,C) (A and (B or C) equ A and B or A and C))
<example in Haskell>
 
  +
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
 
</pre>
 
</pre>
   
  +
Example in Haskell:
Solution:
 
  +
 
<haskell>
 
<haskell>
  +
λ> tablen 3 (\[a,b,c] -> a `and'` (b `or'` c) `equ'` a `and'` b `or'` a `and'` c)
<solution in haskell>
 
  +
-- infixl 3 `equ'`
  +
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
  +
  +
-- infixl 7 `equ'`
  +
True True True True
  +
True True False True
  +
True False True True
  +
True False False False
  +
False True True False
  +
False True False False
  +
False False True False
  +
False False False False
 
</haskell>
 
</haskell>
   
  +
<description of implementation>
 
 
 
== Problem 49 ==
 
== Problem 49 ==
  +
<div style="border-bottom:1px solid #eee">(**) Gray codes. <span style="float:right"><small>[[99 questions/Solutions/49|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
 
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 115: Line 127:
 
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>
  +
λ> gray 3
gray :: Int -> [String]
 
  +
["000","001","011","010","110","111","101","100"]
gray 1 = ["0", "1"]
 
gray (n+1) = let xs = gray n in map ('0':) xs ++ map ('1':) (reverse xs)
 
 
</haskell>
 
</haskell>
 
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 perpend a 1 to each word. At last we have to append these two lists. (Wikipedia seems to approve this.)
 
 
Instead of the equation for <hask>gray 1 = ...</hask> we could also use
 
<haskell>
 
gray 0 = [""]
 
</haskell>
 
what leads to the same results.
 
   
 
 
 
== Problem 50 ==
 
== Problem 50 ==
  +
<div style="border-bottom:1px solid #eee">(***) Huffman codes. <span style="float:right"><small>[[99 questions/Solutions/50|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
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:
<Problem description>
 
   
 
<pre>
 
<pre>
  +
% huffman(Fs,Hs) :- Hs is the Huffman code table for the frequency table Fs
Example:
 
  +
</pre>
<example in lisp>
 
   
 
Example in Haskell:
 
Example in Haskell:
<example in Haskell>
 
</pre>
 
 
Solution:
 
 
<haskell>
 
<haskell>
  +
λ> huffman [('a',45),('b',13),('c',12),('d',16),('e',9),('f',5)]
<solution in haskell>
 
  +
[('a',"0"),('b',"101"),('c',"100"),('d',"111"),('e',"1101"),('f',"1100")]
 
</haskell>
 
</haskell>
   
<description of implementation>
 
 
   
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Latest revision as of 02:38, 11 June 2023


This is part of Ninety-Nine Haskell Problems, based on Ninety-Nine Prolog Problems.

Logic and Codes

Problem 46

(**) Truth tables for logical expressions. Solutions

 

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:

λ> table (\a b -> (and' a (or' a b)))
True True True
True False True
False True False
False False False


Problem 47

(*) Truth tables for logical expressions (part 2). Solutions

 

Continue Problem 46 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


Problem 48

(*) Truth tables for logical expressions (part 3). Solutions

 

Generalize Problem 47 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)
-- infixl 3 `equ'`
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

-- infixl 7 `equ'`
True  True  True  True
True  True  False True
True  False True  True
True  False False False
False True  True  False
False True  False False
False False True  False
False False False False


Problem 49

(**) Gray codes. Solutions

 

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:

λ> gray 3
["000","001","011","010","110","111","101","100"]


Problem 50

(***) Huffman codes. Solutions

 

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:

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