Difference between revisions of "99 questions/31 to 41"

From HaskellWiki
Jump to navigation Jump to search
m
 
(25 intermediate revisions by 13 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.
 
 
== Arithmetic ==
 
   
 
== Problem 31 ==
 
== Problem 31 ==
  +
<div style="border-bottom:1px solid #eee">(**) Determine whether a given integer number is prime. <span style="float:right"><small>[[99 questions/Solutions/31|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
Example:
Determine whether a given integer number is prime.
 
   
 
<pre>
 
<pre>
Example:
 
 
* (is-prime 7)
 
* (is-prime 7)
 
T
 
T
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
P31> isPrime 7
 
True
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
λ> isPrime 7
isPrime :: Integral a => a -> Bool
 
  +
True
isPrime p = all (\n -> p `mod` n /= 0 ) $ takeWhile (\n -> n*n <= x) [2..]
 
 
</haskell>
 
</haskell>
   
  +
Well, a natural number p is a prime number iff no natural number n with n >= 2 and n^2 <= p is a divisor of p. That's exactly what is implemented: we take the list of all integral numbers starting with 2 as long as their square is at most p and check that for all these n there is a remainder concerning the division of p by n.
 
 
 
 
== Problem 32 ==
 
== Problem 32 ==
  +
<div style="border-bottom:1px solid #eee">(**) Determine the greatest common divisor of two positive integer numbers. <span style="float:right"><small>[[99 questions/Solutions/32|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
Use [http://en.wikipedia.org/wiki/Euclidean_algorithm Euclid's algorithm].
(**) Determine the greatest common divisor of two positive integer numbers.
 
Use Euclid's algorithm.
 
   
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (gcd 36 63)
 
* (gcd 36 63)
 
9
 
9
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
[myGCD 36 63, myGCD (-3) (-6), myGCD (-3) 6]
 
[9,3,3]
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
λ> [myGCD 36 63, myGCD (-3) (-6), myGCD (-3) 6]
gcd' 0 y = y
 
  +
[9,3,3]
gcd' x y = gcd' (y `mod` x) x
 
myGCD x y | x < 0 = myGCD (-x) y
 
| y < 0 = myGCD x (-y)
 
| y < x = gcd' y x
 
| otherwise = gcd' x y
 
 
</haskell>
 
</haskell>
   
The Prelude includes a gcd function, so we have to choose another name for ours. The function gcd' is a straightforward implementation of Euler's algorithm, and myGCD is just a wrapper that makes sure the arguments are positive and in increasing order.
 
   
 
== Problem 33 ==
 
== Problem 33 ==
  +
<div style="border-bottom:1px solid #eee">(*) Determine whether two positive integer numbers are coprime. <span style="float:right"><small>[[99 questions/Solutions/33|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
(*) Determine whether two positive integer numbers are coprime.
 
 
Two numbers are coprime if their greatest common divisor equals 1.
 
Two numbers are coprime if their greatest common divisor equals 1.
 
   
 
Example:
 
Example:
  +
 
<pre>
 
<pre>
 
* (coprime 35 64)
 
* (coprime 35 64)
Line 71: Line 62:
   
 
Example in Haskell:
 
Example in Haskell:
<pre>
 
* coprime 35 64
 
True
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
coprime a b = gcd a b == 1
+
λ> coprime 35 64
  +
True
 
</haskell>
 
</haskell>
   
Here we use the prelude function for computing gcd's along with a test of the result's equality to one.
 
 
 
 
== Problem 34 ==
 
== Problem 34 ==
  +
<div style="border-bottom:1px solid #eee">(**) Calculate Euler's totient function phi(m). <span style="float:right"><small>[[99 questions/Solutions/34|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
(**) Calculate Euler's totient function phi(m).
 
 
Euler's so-called totient function phi(m) is defined as the number of positive integers r (1 <= r < m) that are coprime to m.
 
Euler's so-called totient function phi(m) is defined as the number of positive integers r (1 <= r < m) that are coprime to m.
  +
 
Example: m = 10: r = 1,3,7,9; thus phi(m) = 4. Note the special case: phi(1) = 1.
 
Example: m = 10: r = 1,3,7,9; thus phi(m) = 4. Note the special case: phi(1) = 1.
  +
<pre>
 
 
Example:
 
Example:
  +
  +
<pre>
 
* (totient-phi 10)
 
* (totient-phi 10)
4
 
Example in Haskell:
 
* totient 10
 
 
4
 
4
 
</pre>
 
</pre>
   
  +
Example in Haskell:
Solution:
 
  +
 
<haskell>
 
<haskell>
totient 1 = 1
+
λ> totient 10
  +
4
totient a = length $ filter (coprime a) [1..a-1]
 
where coprime a b = gcd a b == 1
 
 
</haskell>
 
</haskell>
   
  +
We take coprime from the previous exercise and give it to filter, which applies it to each element of a list from 1 to one less than the number, returning only those that are true. lenght tells us how many elements are in the resulting list, and thus how many elements are coprime to n
 
 
 
== Problem 35 ==
 
== Problem 35 ==
  +
<div style="border-bottom:1px solid #eee">(**) Determine the prime factors of a given positive integer. <span style="float:right"><small>[[99 questions/Solutions/35|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
(**) Determine the prime factors of a given positive integer.
 
 
Construct a flat list containing the prime factors in ascending order.
 
Construct a flat list containing the prime factors in ascending order.
  +
  +
Example:
  +
 
<pre>
 
<pre>
Example:
 
 
* (prime-factors 315)
 
* (prime-factors 315)
 
(3 3 5 7)
 
(3 3 5 7)
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
* primeFactors 315
 
[3, 3, 5, 7]
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
primeFactors :: Integer -> [Integer]
+
λ> primeFactors 315
  +
[3, 3, 5, 7]
primeFactors a = let (f, f1) = factorPairOf a
 
f' = if prime f then [f] else primeFactors f
 
f1' = if prime f1 then [f1] else primeFactors f1
 
in f' ++ f1'
 
where
 
factorPairOf a = let f = head $ factors a
 
in (f, div a f)
 
factors a = filter (isFactor a) [2..a-1]
 
isFactor a b = rem a b == 0
 
prime a = (length $ factors a) == 0
 
 
</haskell>
 
</haskell>
   
Kind of ugly, but it works, though it may have bugs in corner cases. This uses the factor tree method of finding prime factors of a number. factorPairOf picks a factor and takes it and the factor you multiply it by and gives them to primeFactors. primeFactors checks to make sure the factors are prime. If not it prime factorizes them. In the end a list of prime factors is returned.
 
 
Another possibility is to observe that you need not enforce the fact that each division be by a prime:
 
<haskell>
 
primefactors n = primefactors' n 2 where
 
primefactors' 1 _ = []
 
primefactors' n dividend = if n `mod` dividend == 0
 
then dividend : primefactors' (n `div` dividend) dividend
 
else primefactors' n (dividend + 1)
 
</haskell>
 
Thus, we just loop through all possible factors and add them to the list if they divide the original number. As the primes get farther apart, though, this will do a lot of needless checks to see if composite numbers are prime factors.
 
 
 
 
== Problem 36 ==
 
== Problem 36 ==
(**) Determine the prime factors of a given positive integer.
+
<div style="border-bottom:1px solid #eee">(**) Determine the prime factors and their multiplicities of a given positive integer. <span style="float:right"><small>[[99 questions/Solutions/36|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
Construct a list containing the prime factors and their multiplicity.
+
Construct a list containing each prime factor and its multiplicity.
  +
  +
Example:
   
 
<pre>
 
<pre>
Example:
 
 
* (prime-factors-mult 315)
 
* (prime-factors-mult 315)
 
((3 2) (5 1) (7 1))
 
((3 2) (5 1) (7 1))
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
*Main> prime_factors_mult 315
 
[(2 3), (1 5), (1 7)]
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
prime_factors_mult n = encode $ prime_factors_mult 2 n []
+
λ> prime_factors_mult 315
  +
[(3,2),(5,1),(7,1)]
prime_factors i n xs = if i*i > n then n:xs else if i `divides` n then prime_factors i (n `div` i) (i:xs) else prime_factors (i+1) n xs
 
divides a b = (b `div` a)*a == b
 
 
</haskell>
 
</haskell>
   
We iterate through all numbers up to the square-root of n, and add them to our list, if they divide n. The function 'encode' is the solution to problem 10. It takes a list of numbers, and compresses it to a list of numbers paired with their multiplicity.
 
 
 
 
== Problem 37 ==
 
== Problem 37 ==
  +
<div style="border-bottom:1px solid #eee">(**) Calculate Euler's totient function phi(m) (improved). <span style="float:right"><small>[[99 questions/Solutions/37|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
See Problem 34 for the definition of Euler's totient function. If the list of the prime factors of a number m is known in the form of problem 36 then the function phi(m) can be efficiently calculated as follows: Let ((p1 m1) (p2 m2) (p3 m3) ...) be the list of prime factors (and their multiplicities) of a given number m. Then phi(m) can be calculated with the following formula:
(**) Calculate Euler's totient function phi(m) (improved).
 
See problem P34 for the definition of Euler's totient function. If the list of the prime factors of a number m is known in the form of problem P36 then the function phi(m) can be efficiently calculated as follows: Let ((p1 m1) (p2 m2) (p3 m3) ...) be the list of prime factors (and their multiplicities) of a given number m. Then phi(m) can be calculated with the following formula:
 
   
 
<pre>
 
<pre>
phi(m) = (p1 - 1) * p1 ** (m1 - 1) + (p2 - 1) * p2 ** (m2 - 1) + (p3 - 1) * p3 ** (m3 - 1) + ...
+
phi(m) = (p1 - 1) * p1 ** (m1 - 1) *
  +
(p2 - 1) * p2 ** (m2 - 1) *
  +
(p3 - 1) * p3 ** (m3 - 1) * ...
 
</pre>
 
</pre>
   
 
Note that a ** b stands for the b'th power of a.
 
Note that a ** b stands for the b'th power of a.
<i>Note</i>: Actually, the official problems show this as a sum, but it should be a product.
 
   
  +
Solution: Given prime_factors_mult from problem 36, we get
 
<haskell>
 
totient m = product [(p - 1) * p ^ (c - 1) | (c, p) <- prime_factors_mult m]
 
</haskell>
 
This just uses a list comprehension to build each term of the product in the formula for phi, then multiplies them all.
 
 
 
== Problem 38 ==
 
== Problem 38 ==
  +
<div style="border-bottom:1px solid #eee">(*) Compare the two methods of calculating Euler's totient function. <span style="float:right"><small>(no solution required)</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
Use the solutions of Problems 34 and 37 to compare the algorithms. Take the number of reductions as a measure for efficiency. Try to calculate phi(10090) as an example.
<Problem description>
 
   
<pre>
 
Example:
 
<example in lisp>
 
 
Example in Haskell:
 
<example in Haskell>
 
</pre>
 
 
Solution:
 
<haskell>
 
<solution in haskell>
 
</haskell>
 
 
<description of implementation>
 
 
 
 
== Problem 39 ==
 
== Problem 39 ==
  +
<div style="border-bottom:1px solid #eee">(*) A list of prime numbers in a given range. <span style="float:right"><small>[[99 questions/Solutions/39|Solutions]]</small></span>
 
  +
</div>
A list of prime numbers.
 
  +
&nbsp;<br>
   
 
Given a range of integers by its lower and upper limit, construct a list of all prime numbers in that range.
 
Given a range of integers by its lower and upper limit, construct a list of all prime numbers in that range.
   
<pre>
 
 
Example in Haskell:
 
Example in Haskell:
P29> primesR 10 20
 
[11,13,17,19]
 
</pre>
 
   
Solution 1:
 
 
<haskell>
 
<haskell>
  +
λ> primesR 10 20
primesR :: Integral a => a -> a -> [a]
 
  +
[11,13,17,19]
primesR a b = filter isPrime [a..b]
 
 
</haskell>
 
</haskell>
   
If we are challenged to give all primes in the range between a and b we simply take all number from a up to b and filter the primes out.
 
   
  +
== Problem 40 ==
Solution 2:
 
  +
<div style="border-bottom:1px solid #eee">(**) Goldbach's conjecture. <span style="float:right"><small>[[99 questions/Solutions/40|Solutions]]</small></span>
<haskell>
 
  +
</div>
primes :: Integral a => [a]
 
  +
&nbsp;<br>
primes = let sieve (n:ns) = n:sieve [ m | m <- ns, m `mod` n /= 0 ] in sieve [2..]
 
   
  +
Goldbach's conjecture says that every positive even number greater than 2 is the sum of two prime numbers. Example: 28 = 5 + 23. It is one of the most famous facts in number theory that has not been proved to be correct in the general case. It has been numerically confirmed up to very large numbers (much larger than we can go with our Prolog system). Write a predicate to find the two prime numbers that sum up to a given even integer.
primesR :: Integral a => a -> a -> [a]
 
primesR a b = takeWhile (<= b) $ dropWhile (< a) primes
 
</haskell>
 
   
  +
Example:
Another way to compute the claimed list is done by using the ''Sieve of Eratosthenes''. The <hask>primes</hask> function generates a list of all (!) prime numbers using this algorithm and <hask>primesR</hask> filter the relevant range out. [But this way is very slow and I only presented it because I wanted to show how nice the ''Sieve of Eratosthenes'' can be implemented in Haskell :)]
 
 
== Problem 40 ==
 
(**) Goldbach's conjecture.
 
Goldbach's conjecture says that every positive even number greater than 2 is the sum of two prime numbers. Example: 28 = 5 + 23. It is one of the most famous facts in number theory that has not been proved to be correct in the general case. It has been numerically confirmed up to very large numbers (much larger than we can go with our Prolog system). Write a predicate to find the two prime numbers that sum up to a given even integer.
 
   
 
<pre>
 
<pre>
Example:
 
 
* (goldbach 28)
 
* (goldbach 28)
(5 23)<Problem description>
+
(5 23)
  +
</pre>
   
 
Example in Haskell:
 
Example in Haskell:
*goldbach 28
 
(5, 23)
 
</pre>
 
   
Solution:
 
 
<haskell>
 
<haskell>
goldbach a = head $
+
λ> goldbach 28
  +
(5, 23)
filter (\e -> (isPrime $ fst e) && (isPrime $ snd e)) $
 
map (\e -> (e, a - e)) [1,3..div a 2]
 
where
 
factors a = filter (isFactor a) [2..a-1]
 
isFactor a b = rem a b == 0
 
isPrime a = (length $ factors a) == 0
 
 
</haskell>
 
</haskell>
   
  +
Woohoo! I've solved the goldbach conjecture! Where do I collect my prize? This the obvious thing. It makes a list of odd numbers and then uses it to make up pairs of odd numbers that sum to n. Then it looks for a pair of odd numbers where both are prime and returns it as a tuple.
 
 
 
== Problem 41 ==
 
== Problem 41 ==
  +
<div style="border-bottom:1px solid #eee">(**) A list of even numbers and their Goldbach compositions in a given range. <span style="float:right"><small>[[99 questions/Solutions/41|Solutions]]</small></span>
  +
</div>
  +
&nbsp;<br>
   
  +
Given a range of integers by its lower and upper limit, print a list of all even numbers and their Goldbach composition.
<Problem description>
 
  +
  +
In most cases, if an even number is written as the sum of two prime numbers, one of them is very small. Very rarely, the primes are both bigger than say 50. Try to find out how many such cases there are in the range 2..3000.
   
<pre>
 
 
Example:
 
Example:
<example in lisp>
 
   
  +
<pre>
Example in Haskell:
 
  +
* (goldbach-list 9 20)
<example in Haskell>
 
  +
10 = 3 + 7
  +
12 = 5 + 7
  +
14 = 3 + 11
  +
16 = 3 + 13
  +
18 = 5 + 13
  +
20 = 3 + 17
  +
* (goldbach-list 1 2000 50)
  +
992 = 73 + 919
  +
1382 = 61 + 1321
  +
1856 = 67 + 1789
  +
1928 = 61 + 1867
 
</pre>
 
</pre>
   
  +
Example in Haskell:
Solution:
 
  +
 
<haskell>
 
<haskell>
  +
λ> goldbachList 9 20
<solution in haskell>
 
  +
[(3,7),(5,7),(3,11),(3,13),(5,13),(3,17)]
  +
λ> goldbachList' 4 2000 50
  +
[(73,919),(61,1321),(67,1789),(61,1867)]
 
</haskell>
 
</haskell>
   
<description of implementation>
 
   
 
[[Category:Tutorials]]
 
[[Category:Tutorials]]

Latest revision as of 02:30, 11 June 2023


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


Problem 31

(**) Determine whether a given integer number is prime. Solutions

 

Example:

* (is-prime 7)
T

Example in Haskell:

λ> isPrime 7
True


Problem 32

(**) Determine the greatest common divisor of two positive integer numbers. Solutions

 

Use Euclid's algorithm.

Example:

* (gcd 36 63)
9

Example in Haskell:

λ> [myGCD 36 63, myGCD (-3) (-6), myGCD (-3) 6]
[9,3,3]


Problem 33

(*) Determine whether two positive integer numbers are coprime. Solutions

 

Two numbers are coprime if their greatest common divisor equals 1.

Example:

* (coprime 35 64)
T

Example in Haskell:

λ> coprime 35 64
True


Problem 34

(**) Calculate Euler's totient function phi(m). Solutions

 

Euler's so-called totient function phi(m) is defined as the number of positive integers r (1 <= r < m) that are coprime to m.

Example: m = 10: r = 1,3,7,9; thus phi(m) = 4. Note the special case: phi(1) = 1.

Example:

* (totient-phi 10)
4

Example in Haskell:

λ> totient 10
4


Problem 35

(**) Determine the prime factors of a given positive integer. Solutions

 

Construct a flat list containing the prime factors in ascending order.

Example:

* (prime-factors 315)
(3 3 5 7)

Example in Haskell:

λ> primeFactors 315
[3, 3, 5, 7]


Problem 36

(**) Determine the prime factors and their multiplicities of a given positive integer. Solutions

 

Construct a list containing each prime factor and its multiplicity.

Example:

* (prime-factors-mult 315)
((3 2) (5 1) (7 1))

Example in Haskell:

λ> prime_factors_mult 315
[(3,2),(5,1),(7,1)]


Problem 37

(**) Calculate Euler's totient function phi(m) (improved). Solutions

 

See Problem 34 for the definition of Euler's totient function. If the list of the prime factors of a number m is known in the form of problem 36 then the function phi(m) can be efficiently calculated as follows: Let ((p1 m1) (p2 m2) (p3 m3) ...) be the list of prime factors (and their multiplicities) of a given number m. Then phi(m) can be calculated with the following formula:

phi(m) = (p1 - 1) * p1 ** (m1 - 1) * 
         (p2 - 1) * p2 ** (m2 - 1) * 
         (p3 - 1) * p3 ** (m3 - 1) * ...

Note that a ** b stands for the b'th power of a.


Problem 38

(*) Compare the two methods of calculating Euler's totient function. (no solution required)

 

Use the solutions of Problems 34 and 37 to compare the algorithms. Take the number of reductions as a measure for efficiency. Try to calculate phi(10090) as an example.


Problem 39

(*) A list of prime numbers in a given range. Solutions

 

Given a range of integers by its lower and upper limit, construct a list of all prime numbers in that range.

Example in Haskell:

λ> primesR 10 20
[11,13,17,19]


Problem 40

(**) Goldbach's conjecture. Solutions

 

Goldbach's conjecture says that every positive even number greater than 2 is the sum of two prime numbers. Example: 28 = 5 + 23. It is one of the most famous facts in number theory that has not been proved to be correct in the general case. It has been numerically confirmed up to very large numbers (much larger than we can go with our Prolog system). Write a predicate to find the two prime numbers that sum up to a given even integer.

Example:

* (goldbach 28)
(5 23)

Example in Haskell:

λ> goldbach 28
(5, 23)


Problem 41

(**) A list of even numbers and their Goldbach compositions in a given range. Solutions

 

Given a range of integers by its lower and upper limit, print a list of all even numbers and their Goldbach composition.

In most cases, if an even number is written as the sum of two prime numbers, one of them is very small. Very rarely, the primes are both bigger than say 50. Try to find out how many such cases there are in the range 2..3000.

Example:

* (goldbach-list 9 20)
10 = 3 + 7
12 = 5 + 7
14 = 3 + 11
16 = 3 + 13
18 = 5 + 13
20 = 3 + 17
* (goldbach-list 1 2000 50)
992 = 73 + 919
1382 = 61 + 1321
1856 = 67 + 1789
1928 = 61 + 1867

Example in Haskell:

λ> goldbachList 9 20
[(3,7),(5,7),(3,11),(3,13),(5,13),(3,17)]
λ> goldbachList' 4 2000 50
[(73,919),(61,1321),(67,1789),(61,1867)]