Difference between revisions of "Euler problems/1 to 10"
Marypoppins (talk | contribs) |
CaleGibbard (talk | contribs) (rv: vandalism) |
||
Line 1: | Line 1: | ||
− | + | == [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. | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | problem_1 = | ||
+ | sum [ x | | ||
+ | x <- [1..999], | ||
+ | (x `mod` 3 == 0) || (x `mod` 5 == 0) | ||
+ | ] | ||
+ | </haskell> | ||
+ | |||
+ | <haskell> | ||
+ | problem_1_v2 = | ||
+ | sum $ filter (\x -> ( x `mod` 3 == 0 || x `mod` 5 == 0 ) ) [1..999] | ||
+ | </haskell> | ||
+ | ---- | ||
+ | <haskell> | ||
+ | sumOnetoN n = n * (n+1) `div` 2 | ||
+ | |||
+ | problem_1 = | ||
+ | sumStep 3 999 + sumStep 5 999 - sumStep 15 999 | ||
+ | where | ||
+ | sumStep s n = s * sumOnetoN (n `div` s) | ||
+ | |||
+ | </haskell> | ||
+ | |||
+ | == [http://projecteuler.net/index.php?section=view&id=2 Problem 2] == | ||
+ | Find the sum of all the even-valued terms in the Fibonacci sequence which do not exceed one million. | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | problem_2 = | ||
+ | sum [ x | | ||
+ | x <- takeWhile (<= 1000000) fibs, | ||
+ | x `mod` 2 == 0 | ||
+ | ] | ||
+ | where | ||
+ | fibs = 1 : 1 : zipWith (+) fibs (tail fibs) | ||
+ | </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> | ||
+ | problem_2_v2 = | ||
+ | sumEvenFibs $ numEvenFibsLessThan 1000000 | ||
+ | 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) | ||
+ | </haskell> | ||
+ | |||
+ | 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): | ||
+ | <haskell> | ||
+ | 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) | ||
+ | </haskell> | ||
+ | |||
+ | == [http://projecteuler.net/index.php?section=view&id=3 Problem 3] == | ||
+ | Find the largest prime factor of 317584931803. | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | 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_3 = | ||
+ | last (primeFactors 317584931803) | ||
+ | </haskell> | ||
+ | |||
+ | 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. | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | problem_4 = | ||
+ | foldr max 0 [ x | | ||
+ | y <- [100..999], | ||
+ | z <- [100..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> | ||
+ | |||
+ | == [http://projecteuler.net/index.php?section=view&id=5 Problem 5] == | ||
+ | What is the smallest number divisible by each of the numbers 1 to 20? | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | problem_5 = | ||
+ | head [ x | | ||
+ | x <- [2520,5040..], | ||
+ | all (\y -> x `mod` y == 0) [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> | ||
+ | |||
+ | == [http://projecteuler.net/index.php?section=view&id=6 Problem 6] == | ||
+ | What is the difference between the sum of the squares and the square of the sums? | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | problem_6 = | ||
+ | sum [ x^2 | x <- [1..100]] - (sum [1..100])^2 | ||
+ | </haskell> | ||
+ | |||
+ | == [http://projecteuler.net/index.php?section=view&id=7 Problem 7] == | ||
+ | Find the 10001st prime. | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | --primes in problem_3 | ||
+ | problem_7 = | ||
+ | head $ drop 10000 primes | ||
+ | </haskell> | ||
+ | |||
+ | As above, this can be improved by using | ||
+ | <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]: | ||
+ | |||
+ | <haskell> | ||
+ | primes' = | ||
+ | 2 : 3 : sieve (tail primes') [5,7..] | ||
+ | where | ||
+ | sieve (p:ps) x = | ||
+ | h ++ sieve ps (filter (\q -> q `mod` p /= 0) t | ||
+ | where | ||
+ | (h, _:t) = span (p*p <) x | ||
+ | problem_7_v2 = primes' !! 10000 | ||
+ | </haskell> | ||
+ | |||
+ | == [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: | ||
+ | <haskell> | ||
+ | import Data.Char | ||
+ | groupsOf _ [] = [] | ||
+ | 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 $foldl (++) "" $ lines t | ||
+ | print $ problem_8 digits | ||
+ | </haskell> | ||
+ | |||
+ | == [http://projecteuler.net/index.php?section=view&id=9 Problem 9] == | ||
+ | There is only one Pythagorean triplet, {''a'', ''b'', ''c''}, for which ''a'' + ''b'' + ''c'' = 1000. Find the product ''abc''. | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | problem_9 = | ||
+ | head [a*b*c | | ||
+ | a <- [1..500], | ||
+ | b <- [a..500], | ||
+ | let c = 1000-a-b, | ||
+ | a^2 + b^2 == c^2 | ||
+ | ] | ||
+ | </haskell> | ||
+ | |||
+ | Another solution using Pythagorean Triplets generation: | ||
+ | <haskell> | ||
+ | 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 | ||
+ | </haskell> | ||
+ | |||
+ | == [http://projecteuler.net/index.php?section=view&id=10 Problem 10] == | ||
+ | Calculate the sum of all the primes below one million. | ||
+ | |||
+ | Solution: | ||
+ | <haskell> | ||
+ | problem_10 = | ||
+ | sum (takeWhile (< 1000000) primes) | ||
+ | </haskell> |
Revision as of 04:53, 30 January 2008
Contents
Problem 1
Add all the natural numbers below 1000 that are multiples of 3 or 5.
Solution:
problem_1 =
sum [ x |
x <- [1..999],
(x `mod` 3 == 0) || (x `mod` 5 == 0)
]
problem_1_v2 =
sum $ filter (\x -> ( x `mod` 3 == 0 || x `mod` 5 == 0 ) ) [1..999]
sumOnetoN n = n * (n+1) `div` 2
problem_1 =
sumStep 3 999 + sumStep 5 999 - sumStep 15 999
where
sumStep s n = s * sumOnetoN (n `div` s)
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,
x `mod` 2 == 0
]
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_v2 =
sumEvenFibs $ numEvenFibsLessThan 1000000
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 317584931803.
Solution:
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_3 =
last (primeFactors 317584931803)
This can be improved by using
null . tail
instead of
(== 1) . length
.
Problem 4
Find the largest palindrome made from the product of two 3-digit numbers.
Solution:
problem_4 =
foldr max 0 [ x |
y <- [100..999],
z <- [100..999],
let x = y * z,
let s = show x,
s == reverse s
]
An alternative to avoid evaluating twice the same pair of numbers:
problem_4' =
foldr1 max [ 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 =
head [ x |
x <- [2520,5040..],
all (\y -> x `mod` y == 0) [1..20]
]
An alternative solution that takes advantage of the Prelude to avoid use of the generate and test idiom:
problem_5' = foldr1 lcm [1..20]
Problem 6
What is the difference between the sum of the squares and the square of the sums?
Solution:
problem_6 =
sum [ x^2 | x <- [1..100]] - (sum [1..100])^2
Problem 7
Find the 10001st prime.
Solution:
--primes in problem_3
problem_7 =
head $ drop 10000 primes
As above, this can be improved by using
null . tail
instead of
(== 1) . length
.
Here is an alternative that uses a sieve of Eratosthenes:
primes' =
2 : 3 : sieve (tail primes') [5,7..]
where
sieve (p:ps) x =
h ++ sieve ps (filter (\q -> q `mod` p /= 0) t
where
(h, _:t) = span (p*p <) x
problem_7_v2 = primes' !! 10000
Problem 8
Discover the largest product of five consecutive digits in the 1000-digit number.
Solution:
import Data.Char
groupsOf _ [] = []
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 $foldl (++) "" $ lines t
print $ problem_8 digits
Problem 9
There is only one Pythagorean triplet, {a, b, c}, for which a + b + c = 1000. Find the product abc.
Solution:
problem_9 =
head [a*b*c |
a <- [1..500],
b <- [a..500],
let c = 1000-a-b,
a^2 + b^2 == c^2
]
Another solution using Pythagorean Triplets generation:
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:
problem_10 =
sum (takeWhile (< 1000000) primes)