Difference between revisions of "Euler problems/1 to 10"

From HaskellWiki
Jump to navigation Jump to search
(Use null.tail or sieve to find primes)
(48 intermediate revisions by 14 users not shown)
Line 1: Line 1:
  +
== [http://projecteuler.net/index.php?section=problems&id=1 Problem 1] ==
[[Category:Programming exercise spoilers]]
 
== [http://projecteuler.net/index.php?section=view&id=1 Problem 1] ==
 
 
Add all the natural numbers below 1000 that are multiples of 3 or 5.
 
Add all the natural numbers below 1000 that are multiples of 3 or 5.
   
  +
Two solutions using <hask>sum</hask>:
Solution:
 
 
<haskell>
 
<haskell>
  +
import Data.List (union)
problem_1 = sum [ x | x <- [1..999], (x `mod` 3 == 0) || (x `mod` 5 == 0)]
 
  +
problem_1' = sum (union [3,6..999] [5,10..999])
  +
  +
problem_1 = sum [x | x <- [1..999], x `mod` 3 == 0 || x `mod` 5 == 0]
 
</haskell>
 
</haskell>
  +
  +
Another solution which uses algebraic relationships:
   
 
<haskell>
 
<haskell>
  +
problem_1 = sumStep 3 999 + sumStep 5 999 - sumStep 15 999
problem_1_v2 = sum $ filter (\x -> ( x `mod` 3 == 0 || x `mod` 5 == 0 ) ) [1..999]
 
  +
where
</haskell>
 
  +
sumStep s n = s * sumOnetoN (n `div` s)
----
 
  +
sumOnetoN n = n * (n+1) `div` 2
<haskell>
 
sum1to n = n * (n+1) `div` 2
 
 
problem_1_v3 = sumStep 3 999 + sumStep 5 999 - sumStep 15 999
 
where sumStep s n = s * sum1to (n `div` s)
 
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=2 Problem 2] ==
+
== [http://projecteuler.net/index.php?section=problems&id=2 Problem 2] ==
 
Find the sum of all the even-valued terms in the Fibonacci sequence which do not exceed one million.
 
Find the sum of all the even-valued terms in the Fibonacci sequence which do not exceed one million.
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
problem_2 = sum [ x | x <- takeWhile (<= 1000000) fibs, x `mod` 2 == 0]
+
problem_2 = sum [ x | x <- takeWhile (<= 1000000) fibs, even x]
  +
where
where fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
 
  +
fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
 
</haskell>
 
</haskell>
  +
----
 
  +
The following two solutions use the fact that the even-valued terms in
  +
the Fibonacci sequence themselves form a Fibonacci-like sequence
  +
that satisfies
  +
<hask>evenFib 0 = 0, evenFib 1 = 2, evenFib (n+2) = evenFib n + 4 * evenFib (n+1)</hask>.
 
<haskell>
 
<haskell>
problem_2_v2 = sumEvenFibs $ numEvenFibsLessThan 1000000
+
problem_2 = sumEvenFibs $ numEvenFibsLessThan 1000000
  +
where
sumEvenFibs n = (evenFib n + evenFib (n+1) - 2) `div` 4
 
  +
sumEvenFibs n = (evenFib n + evenFib (n+1) - 2) `div` 4
evenFib n = round $ (2 + sqrt 5) ** (fromIntegral n) / sqrt 5
 
  +
evenFib n = round $ (2 + sqrt 5) ** (fromIntegral n) / sqrt 5
numEvenFibsLessThan n =
 
  +
numEvenFibsLessThan n =
floor $ (log (fromIntegral n - 0.5) + 0.5*log 5) / log (2 + sqrt 5)
 
  +
floor $ (log (fromIntegral n - 0.5) + 0.5*log 5) / log (2 + sqrt 5)
 
</haskell>
 
</haskell>
   
This works because 10^6 is small. To work with large numbers,
+
The first two solutions work because 10^6 is small.
  +
The following solution also works for much larger numbers
where using Double is not possible, you can define evenFib
 
  +
(up to at least 10^1000000 on my computer):
and numEvenFibsLessThan by using the identities:
 
  +
<haskell>
  +
problem_2 = sumEvenFibsLessThan 1000000
   
  +
sumEvenFibsLessThan n = (a + b - 1) `div` 2
<haskell>
 
  +
where
2 * evenFib (2*n+1) == evenFib n ^2 + evenFib (n+1) ^ 2
 
  +
n2 = n `div` 2
2 * evenFib (2*n) == evenFib n * evenFib (n+1) - 2 * evenFib n ^ 2
 
  +
(a, b) = foldr f (0,1)
  +
. takeWhile ((<= n2) . fst)
  +
. iterate times2E $ (1, 4)
  +
f x y | fst z <= n2 = z
  +
| otherwise = y
  +
where z = x `addE` y
  +
addE (a, b) (c, d) = (a*d + b*c - 4*ac, ac + b*d)
  +
where ac=a*c
  +
  +
times2E (a, b) = addE (a, b) (a, b)
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=3 Problem 3] ==
+
== [http://projecteuler.net/index.php?section=problems&id=3 Problem 3] ==
Find the largest prime factor of 317584931803.
+
Find the largest prime factor of 600851475143.
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
+
primes = 2 : filter (null . tail . primeFactors) [3,5..]
  +
 
primeFactors n = factor n primes
 
primeFactors n = factor n primes
  +
where
where factor n (p:ps) | p*p > n = [n]
 
| n `mod` p == 0 = p : factor (n `div` p) (p:ps)
+
factor n (p:ps)
| otherwise = factor n ps
+
| p*p > n = [n]
  +
| n `mod` p == 0 = p : factor (n `div` p) (p:ps)
  +
| otherwise = factor n ps
   
problem_3 = last (primeFactors 317584931803)
+
problem_3 = last (primeFactors 600851475143)
 
</haskell>
 
</haskell>
   
  +
== [http://projecteuler.net/index.php?section=problems&id=4 Problem 4] ==
This can be improved by using
 
<hask>null . tail</hask>
 
instead of
 
<hask>(== 1) . length</hask>.
 
 
== [http://projecteuler.net/index.php?section=view&id=4 Problem 4] ==
 
 
Find the largest palindrome made from the product of two 3-digit numbers.
 
Find the largest palindrome made from the product of two 3-digit numbers.
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
problem_4 =
problem_4 = foldr max 0 [ x | y <- [100..999], z <- [100..999], let x = y * z, let s = show x, s == reverse s]
 
  +
maximum [x | y<-[100..999], z<-[y..999], let x=y*z, let s=show x, s==reverse s]
</haskell>
 
An alternative to avoid evaluating twice the same pair of numbers:
 
<haskell>
 
problem_4' = foldr1 max [ x | y <- [100..999], z <- [y..999], let x = y * z, let s = show x, s == reverse s]
 
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=5 Problem 5] ==
+
== [http://projecteuler.net/index.php?section=problems&id=5 Problem 5] ==
 
What is the smallest number divisible by each of the numbers 1 to 20?
 
What is the smallest number divisible by each of the numbers 1 to 20?
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
problem_5 = head [ x | x <- [2520,5040..], all (\y -> x `mod` y == 0) [1..20]]
+
problem_5 = foldr1 lcm [1..20]
</haskell>
 
An alternative solution that takes advantage of the Prelude to avoid use of the generate and test idiom:
 
<haskell>
 
problem_5' = foldr1 lcm [1..20]
 
 
</haskell>
 
</haskell>
   
  +
Another solution: <code>16*9*5*7*11*13*17*19</code>. Product of maximal powers of primes in the range.
== [http://projecteuler.net/index.php?section=view&id=6 Problem 6] ==
 
  +
  +
== [http://projecteuler.net/index.php?section=problems&id=6 Problem 6] ==
 
What is the difference between the sum of the squares and the square of the sums?
 
What is the difference between the sum of the squares and the square of the sums?
   
 
Solution:
 
Solution:
  +
<!--
 
<haskell>
 
<haskell>
  +
fun n = a - b
problem_6 = sum [ x^2 | x <- [1..100]] - (sum [1..100])^2
 
  +
where
  +
a=(n^2 * (n+1)^2) `div` 4
  +
b=(n * (n+1) * (2*n+1)) `div` 6
  +
  +
problem_6 = fun 100
 
</haskell>
 
</haskell>
  +
-->
  +
<!-- Might just be me, but I find this a LOT easier to read. Perhaps not as good mathematically, but it runs in an instant, even for n = 25000.
  +
<haskell>
  +
fun n = a - b
  +
where
  +
a = (sum [1..n])^2
  +
b = sum (map (^2) [1..n])
   
  +
problem_6 = fun 100
== [http://projecteuler.net/index.php?section=view&id=7 Problem 7] ==
 
  +
</haskell>
Find the 10001st prime.
 
  +
-->
 
  +
<!-- I just made it a oneliner... -->
Solution:
 
 
<haskell>
 
<haskell>
  +
problem_6 = (sum [1..100])^2 - sum (map (^2) [1..100])
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
 
primeFactors n = factor n primes
 
where factor n (p:ps) | p*p > n = [n]
 
| n `mod` p == 0 = p : factor (n `div` p) (p:ps)
 
| otherwise = factor n ps
 
problem_7 = head $ drop 10000 primes
 
 
</haskell>
 
</haskell>
   
  +
== [http://projecteuler.net/index.php?section=problems&id=7 Problem 7] ==
As above, this can be improved by using
 
  +
Find the 10001st prime.
<hask>null . tail</hask>
 
instead of
 
<hask>(== 1) . length</hask>.
 
 
Here is an alternative that uses a
 
[http://www.haskell.org/pipermail/haskell-cafe/2007-February/022854.html sieve of Eratosthenes]:
 
   
  +
Solution:
 
<haskell>
 
<haskell>
  +
--primes in problem_3
primes' = 2 : 3 : sieve (tail primes') [5,7..]
 
  +
problem_7 = primes !! 10000
where
 
sieve (p:ps) x = let (h, _:t) = span (p*p <) x
 
in h ++ sieve ps (filter (\q -> q `mod` p /= 0) t
 
problem_7_v2 = primes' !! 10000
 
 
</haskell>
 
</haskell>
  +
== [http://projecteuler.net/index.php?section=problems&id=8 Problem 8] ==
 
  +
Discover the largest product of thirteen consecutive digits in the 1000-digit number.
== [http://projecteuler.net/index.php?section=view&id=8 Problem 8] ==
 
Discover the largest product of five consecutive digits in the 1000-digit number.
 
   
 
Solution:
 
Solution:
  +
<!--
 
<haskell>
 
<haskell>
  +
import Data.Char
num = ... -- 1000 digit number as a string
 
  +
groupsOf _ [] = [] -- incorrect, overall: last
digits = map digitToInt num
 
  +
groupsOf n xs = -- subsequences will be shorter than n!!
 
groupsOf _ [] = []
+
take n xs : groupsOf n ( tail xs )
  +
groupsOf n xs = take n xs : groupsOf n ( tail xs )
 
  +
problem_8 x = maximum . map product . groupsOf 5 $ x
  +
main = do t <- readFile "p8.log"
  +
let digits = map digitToInt $concat $ lines t
  +
print $ problem_8 digits
  +
</haskell>
  +
-->
  +
<haskell>
  +
import Data.Char
  +
import Data.List
   
  +
euler_8 = do
problem_8 = maximum . map product . groupsOf 5 $ digits
 
  +
str <- readFile "number.txt"
  +
print . maximum . map product
  +
. foldr (zipWith (:)) (repeat [])
  +
. take 13 . tails . map (fromIntegral . digitToInt)
  +
. concat . lines $ str
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=9 Problem 9] ==
+
== [http://projecteuler.net/index.php?section=problems&id=9 Problem 9] ==
 
There is only one Pythagorean triplet, {''a'', ''b'', ''c''}, for which ''a'' + ''b'' + ''c'' = 1000. Find the product ''abc''.
 
There is only one Pythagorean triplet, {''a'', ''b'', ''c''}, for which ''a'' + ''b'' + ''c'' = 1000. Find the product ''abc''.
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
triplets l = [[a,b,c] | m <- [2..limit],
problem_9 = head [a*b*c | a <- [1..500], b <- [a..500], let c = 1000-a-b, a^2 + b^2 == c^2]
 
  +
n <- [1..(m-1)],
</haskell>
 
  +
let a = m^2 - n^2,
  +
let b = 2*m*n,
  +
let c = m^2 + n^2,
  +
a+b+c==l]
  +
where limit = floor . sqrt . fromIntegral $ l
   
  +
problem_9 = product . head . triplets $ 1000
Another solution using Pythagorean Triplets generation:
 
<haskell>
 
triplets :: Int -> [(Int, Int, Int)]
 
triplets l = [(a,b,c)|m <- [2..limit], n <- [1..(m-1)], let a = m^2 - n^2, let b = 2*m*n, let c = m^2 + n^2]
 
where limit = floor $ sqrt $ fromIntegral l
 
 
tripletWithLength :: Int -> [(Int, Int, Int)]
 
tripletWithLength n = filter ((==n) . f) $ triplets n
 
where
 
f (a,b,c) = a+b+c
 
 
problem_9 :: Int
 
problem_9 = prod3 $ head $ tripletWithLength 1000
 
where
 
prod3 (a,b,c) = a*b*c
 
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=10 Problem 10] ==
+
== [http://projecteuler.net/index.php?section=problems&id=10 Problem 10] ==
 
Calculate the sum of all the primes below one million.
 
Calculate the sum of all the primes below one million.
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
--primes in problem_3
 
problem_10 = sum (takeWhile (< 1000000) primes)
 
problem_10 = sum (takeWhile (< 1000000) primes)
 
</haskell>
 
</haskell>
 
 
[[Category:Tutorials]]
 
[[Category:Code]]
 

Revision as of 07:05, 3 September 2014

Problem 1

Add all the natural numbers below 1000 that are multiples of 3 or 5.

Two solutions using sum:

import Data.List (union)
problem_1' = sum (union [3,6..999] [5,10..999])

problem_1  = sum [x | x <- [1..999], x `mod` 3 == 0 || x `mod` 5 == 0]

Another solution which uses algebraic relationships:

problem_1 = sumStep 3 999 + sumStep 5 999 - sumStep 15 999
  where
    sumStep s n = s * sumOnetoN (n `div` s)
    sumOnetoN n = n * (n+1) `div` 2

Problem 2

Find the sum of all the even-valued terms in the Fibonacci sequence which do not exceed one million.

Solution:

problem_2 = sum [ x | x <- takeWhile (<= 1000000) fibs, even x]
  where
    fibs = 1 : 1 : zipWith (+) fibs (tail fibs)

The following two solutions use the fact that the even-valued terms in the Fibonacci sequence themselves form a Fibonacci-like sequence that satisfies evenFib 0 = 0, evenFib 1 = 2, evenFib (n+2) = evenFib n + 4 * evenFib (n+1).

problem_2 = sumEvenFibs $ numEvenFibsLessThan 1000000
  where
    sumEvenFibs n = (evenFib n + evenFib (n+1) - 2) `div` 4
    evenFib n = round $ (2 + sqrt 5) ** (fromIntegral n) / sqrt 5
    numEvenFibsLessThan n =
              floor $ (log (fromIntegral n - 0.5) + 0.5*log 5) / log (2 + sqrt 5)

The first two solutions work because 10^6 is small. The following solution also works for much larger numbers (up to at least 10^1000000 on my computer):

problem_2 = sumEvenFibsLessThan 1000000

sumEvenFibsLessThan n = (a + b - 1) `div` 2
  where
    n2 = n `div` 2
    (a, b) = foldr f (0,1)
             . takeWhile ((<= n2) . fst)
             . iterate times2E $ (1, 4)
    f x y | fst z <= n2 = z
          | otherwise   = y
      where z = x `addE` y
addE (a, b) (c, d) = (a*d + b*c - 4*ac, ac + b*d)
  where ac=a*c

times2E (a, b) = addE (a, b) (a, b)

Problem 3

Find the largest prime factor of 600851475143.

Solution:

primes = 2 : filter (null . tail . primeFactors) [3,5..]

primeFactors n = factor n primes
  where
    factor n (p:ps) 
        | p*p > n        = [n]
        | n `mod` p == 0 = p : factor (n `div` p) (p:ps)
        | otherwise      =     factor n ps

problem_3 = last (primeFactors 600851475143)

Problem 4

Find the largest palindrome made from the product of two 3-digit numbers.

Solution:

problem_4 =
  maximum [x | y<-[100..999], z<-[y..999], let x=y*z, let s=show x, s==reverse s]

Problem 5

What is the smallest number divisible by each of the numbers 1 to 20?

Solution:

problem_5 = foldr1 lcm [1..20]

Another solution: 16*9*5*7*11*13*17*19. Product of maximal powers of primes in the range.

Problem 6

What is the difference between the sum of the squares and the square of the sums?

Solution:

problem_6 = (sum [1..100])^2 - sum (map (^2) [1..100])

Problem 7

Find the 10001st prime.

Solution:

--primes in problem_3
problem_7 = primes !! 10000

Problem 8

Discover the largest product of thirteen consecutive digits in the 1000-digit number.

Solution:

import Data.Char 
import Data.List 

euler_8 = do
   str <- readFile "number.txt"
   print . maximum . map product
         . foldr (zipWith (:)) (repeat [])
         . take 13 . tails . map (fromIntegral . digitToInt)
         . concat . lines $ str

Problem 9

There is only one Pythagorean triplet, {a, b, c}, for which a + b + c = 1000. Find the product abc.

Solution:

triplets l = [[a,b,c] | m <- [2..limit],
                        n <- [1..(m-1)], 
                        let a = m^2 - n^2, 
                        let b = 2*m*n, 
                        let c = m^2 + n^2,
                        a+b+c==l]
    where limit = floor . sqrt . fromIntegral $ l

problem_9 = product . head . triplets $ 1000

Problem 10

Calculate the sum of all the primes below one million.

Solution:

--primes in problem_3
problem_10 = sum (takeWhile (< 1000000) primes)