Euler problems/1 to 10: Difference between revisions
m (Completed definition of primes in problem 7) |
m (Corrected links to the Euler project) |
||
Line 1: | Line 1: | ||
[[Category:Programming exercise spoilers]] | [[Category:Programming exercise spoilers]] | ||
== [http://projecteuler.net/index.php?section= | == [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. | ||
Line 12: | Line 12: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [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. | Find the sum of all the even-valued terms in the Fibonacci sequence which do not exceed one million. | ||
Line 21: | Line 21: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [http://projecteuler.net/index.php?section=view&id=3 Problem 3] == | ||
Find the largest prime factor of 317584931803. | Find the largest prime factor of 317584931803. | ||
Line 35: | Line 35: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [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. | ||
Line 43: | Line 43: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [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? | What is the smallest number divisible by each of the numbers 1 to 20? | ||
Line 55: | Line 55: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [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? | What is the difference between the sum of the squares and the square of the sums? | ||
Line 63: | Line 63: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [http://projecteuler.net/index.php?section=view&id=7 Problem 7] == | ||
Find the 10001st prime. | Find the 10001st prime. | ||
Line 76: | Line 76: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [http://projecteuler.net/index.php?section=view&id=8 Problem 8] == | ||
Discover the largest product of five consecutive digits in the 1000-digit number. | Discover the largest product of five consecutive digits in the 1000-digit number. | ||
Line 90: | Line 90: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [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''. | There is only one Pythagorean triplet, {''a'', ''b'', ''c''}, for which ''a'' + ''b'' + ''c'' = 1000. Find the product ''abc''. | ||
Line 98: | Line 98: | ||
</haskell> | </haskell> | ||
== [http://projecteuler.net/index.php?section= | == [http://projecteuler.net/index.php?section=view&id=10 Problem 10] == | ||
Calculate the sum of all the primes below one million. | Calculate the sum of all the primes below one million. | ||
Revision as of 10:26, 20 July 2007
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]
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)
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)
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]
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 = 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
Problem 8
Discover the largest product of five consecutive digits in the 1000-digit number.
Solution:
num = ... -- 1000 digit number as a string
digits = map digitToInt num
groupsOf _ [] = []
groupsOf n xs = take n xs : groupsOf n ( tail xs )
problem_8 = maximum . map product . groupsOf 5 $ 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]
Problem 10
Calculate the sum of all the primes below one million.
Solution:
problem_10 = sum (takeWhile (< 1000000) primes)