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

From HaskellWiki
Jump to navigation Jump to search
(Fix bizarre layout.)
Line 5: Line 5:
 
<haskell>
 
<haskell>
 
sumOnetoN n = n * (n+1) `div` 2
 
sumOnetoN n = n * (n+1) `div` 2
problem_1 =
+
problem_1 = sumStep 3 999 + sumStep 5 999 - sumStep 15 999
 
where
sumStep 3 999 + sumStep 5 999 - sumStep 15 999
 
where
 
 
sumStep s n = s * sumOnetoN (n `div` s)
 
sumStep s n = s * sumOnetoN (n `div` s)
 
</haskell>
 
</haskell>
Line 17: Line 16:
 
<haskell>
 
<haskell>
 
problem_2 =
 
problem_2 =
sum [ x |
+
sum [ x | x <- takeWhile (<= 1000000) fibs,
 
x `mod` 2 == 0]
x <- takeWhile (<= 1000000) fibs,
 
x `mod` 2 == 0
 
]
 
 
where
 
where
 
fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
 
fibs = 1 : 1 : zipWith (+) fibs (tail fibs)
Line 30: Line 27:
 
<hask>evenFib 0 = 0, evenFib 1 = 2, evenFib (n+2) = evenFib n + 4 * evenFib (n+1)</hask>.
 
<hask>evenFib 0 = 0, evenFib 1 = 2, evenFib (n+2) = evenFib n + 4 * evenFib (n+1)</hask>.
 
<haskell>
 
<haskell>
problem_2_v2 =
+
problem_2_v2 = sumEvenFibs $ numEvenFibsLessThan 1000000
 
sumEvenFibs n = (evenFib n + evenFib (n+1) - 2) `div` 4
sumEvenFibs $ numEvenFibsLessThan 1000000
 
 
evenFib n = round $ (2 + sqrt 5) ** (fromIntegral n) / sqrt 5
sumEvenFibs n =
 
(evenFib n + evenFib (n+1) - 2) `div` 4
 
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>
   
Line 46: Line 40:
 
problem_2 = sumEvenFibsLessThan 1000000
 
problem_2 = sumEvenFibsLessThan 1000000
   
sumEvenFibsLessThan n =
+
sumEvenFibsLessThan n = (a + b - 1) `div` 2
 
where
(a + b - 1) `div` 2
 
where
 
 
n2 = n `div` 2
 
n2 = n `div` 2
(a, b) =
+
(a, b) = foldr f (0,1)
foldr f (0,1) $
+
. takeWhile ((<= n2) . fst)
takeWhile ((<= n2) . fst) $
+
. iterate times2E $ (1, 4)
iterate times2E (1, 4)
+
f x y | fst z <= n2 = z
f x y
+
| otherwise = y
| fst z <= n2 = z
+
where z = x `addE` y
| otherwise = y
+
addE (a, b) (c, d) = (a*d + b*c - 4*ac, ac + b*d)
where z = x `addE` y
+
where ac=a*c
  +
addE (a, b) (c, d) =
 
(a*d + b*c - 4*ac, ac + b*d)
+
times2E (a, b) = addE (a, b) (a, b)
where
 
ac=a*c
 
times2E (a, b) =
 
addE (a, b) (a, b)
 
 
</haskell>
 
</haskell>
   
Line 71: Line 60:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
 
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
primes =
 
  +
2 : filter ((==1) . length . primeFactors) [3,5..]
 
primeFactors n =
+
primeFactors n = factor n primes
 
where
factor n primes
 
where
 
 
factor n (p:ps)
 
factor n (p:ps)
 
| p*p > n = [n]
 
| p*p > n = [n]
Line 81: Line 69:
 
| otherwise = factor n ps
 
| otherwise = factor n ps
   
problem_3 =
+
problem_3 = last (primeFactors 317584931803)
last (primeFactors 317584931803)
 
 
</haskell>
 
</haskell>
 
== [http://projecteuler.net/index.php?section=problems&id=4 Problem 4] ==
 
== [http://projecteuler.net/index.php?section=problems&id=4 Problem 4] ==
Line 89: Line 76:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
problem_4 =
+
problem_4 = maximum [ x | y <- [100..999],
 
z <- [y..999],
foldr1 max [ x |
 
  +
let x = y * z,
y <- [100..999],
 
 
let s = show x,
z <- [y..999],
 
let x = y * z,
+
s == reverse s ]
let s = show x,
 
s == reverse s
 
]
 
 
</haskell>
 
</haskell>
   
Line 113: Line 97:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
fun n=
+
fun n = a - b
a-b
+
where
where
 
 
a=div (n^2 * (n+1)^2) 4
 
a=div (n^2 * (n+1)^2) 4
 
b=div (n * (n+1) * (2*n+1)) 6
 
b=div (n * (n+1) * (2*n+1)) 6
  +
problem_6=fun 100
+
problem_6 = fun 100
 
</haskell>
 
</haskell>
   
Line 127: Line 111:
 
<haskell>
 
<haskell>
 
--primes in problem_3
 
--primes in problem_3
problem_7 =
+
problem_7 = head $ drop 10000 primes
head $ drop 10000 primes
 
 
</haskell>
 
</haskell>
 
== [http://projecteuler.net/index.php?section=problems&id=8 Problem 8] ==
 
== [http://projecteuler.net/index.php?section=problems&id=8 Problem 8] ==
Line 140: Line 123:
 
take n xs : groupsOf n ( tail xs )
 
take n xs : groupsOf n ( tail xs )
 
 
problem_8 x=
+
problem_8 x = maximum . map product . groupsOf 5 $ x
 
main = do t <- readFile "p8.log"
maximum . map product . groupsOf 5 $ x
 
 
let digits = map digitToInt $foldl (++) "" $ lines t
main=do
 
 
print $ problem_8 digits
t<-readFile "p8.log"
 
let digits = map digitToInt $foldl (++) "" $ lines t
 
print $ problem_8 digits
 
 
</haskell>
 
</haskell>
   
Line 153: Line 134:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
triplets l = [[a,b,c]|
+
triplets l = [[a,b,c] | m <- [2..limit],
m <- [2..limit],
+
n <- [1..(m-1)],
n <- [1..(m-1)],
+
let a = m^2 - n^2,
let a = m^2 - n^2,
+
let b = 2*m*n,
let b = 2*m*n,
+
let c = m^2 + n^2,
let c = m^2 + n^2,
+
a+b+c==l]
 
where limit = floor . sqrt . fromIntegral $ l
a+b+c==l
 
  +
]
 
 
problem_9 = product . head . triplets $ 1000
where limit = floor $ sqrt $ fromIntegral l
 
problem_9 = product $ head $ triplets 1000
 
 
</haskell>
 
</haskell>
   
Line 171: Line 151:
 
<haskell>
 
<haskell>
 
--http://www.research.att.com/~njas/sequences/A046731
 
--http://www.research.att.com/~njas/sequences/A046731
problem_10 =
+
problem_10 = sum (takeWhile (< 1000000) primes)
sum (takeWhile (< 1000000) primes)
 
 
</haskell>
 
</haskell>

Revision as of 19:12, 19 February 2008

Problem 1

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

Solution:

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)

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:

--http://www.research.att.com/~njas/sequences/A003418
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:

fun n = a - b
  where
    a=div (n^2 * (n+1)^2) 4
    b=div (n * (n+1) * (2*n+1)) 6

problem_6 = fun 100

Problem 7

Find the 10001st prime.

Solution:

--primes in problem_3
problem_7 = head $ drop 10000 primes

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:

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:

--http://www.research.att.com/~njas/sequences/A046731
problem_10 = sum (takeWhile (< 1000000) primes)