Euler problems/1 to 10

From HaskellWiki
< Euler problems
Revision as of 02:31, 8 May 2016 by Dushyant (talk | contribs) (Added solution to problem 2)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.

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)


Another elegant, quick solution, based on some background mathematics as in comments:

-- Every third term is even, and every third term beautifully follows:
-- fib n = 4*fib n-3 + fib n-6
evenFibs = 2 : 8 : zipWith (+) (map (4*) (tail evenFibs)) evenFibs

-- So, evenFibs are: e(n) = 4*e(n-1) + e(n-2)
-- [there4]:4e(n)   = e(n+1) - e(n-1)
--          4e(n-1) = e(n)   - e(n-2)
--          4e(n-2) = e(n-1) - e(n-3)
--          ...
--          4e(3)   = e(4)   - e(2)
--          4e(2)   = e(3)   - e(1)
--          4e(1)   = e(2)   - e(0)
--         -------------------------------
-- Total: 4([sum] e(k) - e(0)) = e(n+1) + e(n) - e(1) - e(0)
-- => [sum] e(k) = (e(n+1) + e(n) - e(1) + 3e(0))/4 = 1089154 for
-- first 10 terms

sumEvenFibsBelow :: Int -> Int
sumEvenFibsBelow n = ((last $ take (x+1) evenFibs) +
                      (last $ take x evenFibs) -
                      8 + 6) `div` 4
  where x = length (takeWhile (<= n) evenFibs)

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)