Difference between revisions of "Euler problems/11 to 20"

From HaskellWiki
Jump to navigation Jump to search
(Problem 18)
(→‎Problem 14: streamline code)
 
(34 intermediate revisions by 16 users not shown)
Line 1: Line 1:
[[Category:Programming exercise spoilers]]
 
 
== [http://projecteuler.net/index.php?section=problems&id=11 Problem 11] ==
 
== [http://projecteuler.net/index.php?section=problems&id=11 Problem 11] ==
What is the greatest product of four numbers on the same straight line in the [http://projecteuler.net/index.php?section=view&id=11 20 by 20 grid]?
+
What is the greatest product of four numbers on the same straight line in the [http://projecteuler.net/index.php?section=problems&id=11 20 by 20 grid]?
   
 
Solution:
 
Solution:
  +
using Array and Arrows, for fun :
 
<haskell>
 
<haskell>
  +
import Control.Arrow
problem_11 = undefined
 
  +
import Data.Array
  +
  +
input :: String -> Array (Int,Int) Int
  +
input = listArray ((1,1),(20,20)) . map read . words
  +
  +
senses = [(+1) *** id,(+1) *** (+1), id *** (+1), (+1) *** (\n -> n - 1)]
  +
  +
inArray a i = inRange (bounds a) i
  +
  +
prods :: Array (Int, Int) Int -> [Int]
  +
prods a = [product xs | i <- range $ bounds a,
  +
s <- senses,
  +
let is = take 4 $ iterate s i,
  +
all (inArray a) is,
  +
let xs = map (a!) is]
  +
main = print . maximum . prods . input =<< getContents
 
</haskell>
 
</haskell>
   
Line 13: Line 29:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
--primeFactors in problem_3
 
problem_12 = head $ filter ((> 500) . nDivisors) triangleNumbers
 
problem_12 = head $ filter ((> 500) . nDivisors) triangleNumbers
  +
where nDivisors n = product $ map ((+1) . length) (group (primeFactors n))
where triangleNumbers = scanl1 (+) [1..]
 
nDivisors n = product $ map ((+1) . length) (group (primeFactors n))
+
triangleNumbers = scanl1 (+) [1..]
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
 
 
</haskell>
 
</haskell>
   
Line 28: Line 40:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
nums = ... -- put the numbers in a list
 
  +
main = do xs <- fmap (map read . lines) (readFile "p13.log")
problem_13 = take 10 . show . sum $ nums
 
  +
print . take 10 . show . sum $ xs
 
</haskell>
 
</haskell>
   
Line 36: Line 49:
   
 
Solution:
 
Solution:
  +
<haskell>
  +
import Data.List
  +
  +
problem_14 = j 1000000 where
  +
f :: Int -> Integer -> Int
  +
f k 1 = k
  +
f k n = f (k+1) $ if even n then div n 2 else 3*n + 1
  +
g x y = if snd x < snd y then y else x
  +
h x n = g x (n, f 1 n)
  +
j n = fst $ foldl' h (1,1) [2..n-1]
  +
</haskell>
  +
  +
Faster solution, using unboxed types and parallel computation:
 
<haskell>
 
<haskell>
  +
import Control.Parallel
p14s :: Integer -> [Integer]
 
  +
import Data.Word
p14s n = n : p14s' n
 
  +
where p14s' n = if n' == 1 then [1] else n' : p14s' n'
 
  +
collatzLen :: Int -> Word32 -> Int
where n' = if even n then n `div` 2 else (3*n)+1
 
  +
collatzLen c 1 = c
  +
collatzLen c n = collatzLen (c+1) $ if n `mod` 2 == 0 then n `div` 2 else 3*n+1
  +
  +
pmax x n = x `max` (collatzLen 1 n, n)
   
  +
solve xs = foldl pmax (1,1) xs
problem_14 = fst $ head $ sortBy (\(_,x) (_,y) -> compare y x) [(x, length $ p14s x) | x <- [1 .. 999999]]
 
   
  +
main = print soln
  +
where
  +
s1 = solve [2..500000]
  +
s2 = solve [500001..1000000]
  +
soln = s2 `par` (s1 `pseq` max s1 s2)
 
</haskell>
 
</haskell>
   
Alternate solution, illustrating use of strict folding:
+
Even faster solution, using an Array to memoize length of sequences :
  +
<haskell>
  +
import Data.Array
  +
import Data.List
  +
import Data.Ord (comparing)
  +
  +
syrs n =
  +
a
  +
where
  +
a = listArray (1,n) $ 0 : map syr [2..n]
  +
syr x =
  +
if y <= n then 1 + a ! y else 1 + syr y
  +
where
  +
y = if even x then x `div` 2 else 3 * x + 1
  +
  +
main =
  +
print . maximumBy (comparing snd) . assocs . syrs $ 1000000
  +
</haskell>
  +
  +
<!--
  +
This is a trivial solution without any memoization, right?
  +
  +
Using a list to memoize the lengths
   
 
<haskell>
 
<haskell>
 
import Data.List
 
import Data.List
   
  +
-- computes the sequence for a given n
problem_14 = j 1000000 where
 
  +
l n = n:unfoldr f n where
f :: Int -> Integer -> Int
 
f k 1 = k
+
f 1 = Nothing -- we're done here
f k n = f (k+1) $ if even n then div n 2 else 3*n + 1
+
-- for reasons of speed we do div and mod in one go
g x y = if snd x < snd y then y else x
+
f n = let (d,m)=divMod n 2 in case m of
h x n = g x (n, f 1 n)
+
0 -> Just (d,d) -- n was even
j n = fst $ foldl' h (1,1) [2..n-1]
+
otherwise -> let k = 3*n+1 in Just (k,k) -- n was odd
  +
  +
  +
answer = foldl1' f $ -- computes the maximum of a list of tuples
  +
-- save the length of the sequence and the number generating it in a tuple
  +
[(length $! l x, x) | x <- [1..1000000]] where
  +
f (a,c) (b,d) -- one tuple is greater than other if the first component (=sequence-length) is greater
  +
| a > b = (a,c)
  +
| otherwise = (b,d)
  +
  +
main = print answer
 
</haskell>
 
</haskell>
  +
-->
   
 
== [http://projecteuler.net/index.php?section=problems&id=15 Problem 15] ==
 
== [http://projecteuler.net/index.php?section=problems&id=15 Problem 15] ==
Line 64: Line 132:
   
 
Solution:
 
Solution:
  +
A direct computation:
  +
<haskell>
  +
problem_15 = iterate (scanl1 (+)) (repeat 1) !! 20 !! 20
  +
</haskell>
  +
  +
Thinking about it as a problem in combinatorics:
  +
  +
Each route has exactly 40 steps, with 20 of them horizontal and 20 of
  +
them vertical. We need to count how many different ways there are of
  +
choosing which steps are horizontal and which are vertical. So we have:
  +
 
<haskell>
 
<haskell>
problem_15 = iterate (scanl1 (+)) (repeat 1) !! 20 !! 20
+
problem_15 = product [21..40] `div` product [2..20]
 
</haskell>
 
</haskell>
   
Line 73: Line 152:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import Data.Char
problem_16 = sum.(map (read.(:[]))).show $ 2^1000
 
  +
problem_16 = sum k
  +
where s = show (2^1000)
  +
k = map digitToInt s
 
</haskell>
 
</haskell>
   
Line 81: Line 163:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import Char
-- not a very concise or beautiful solution, but food for improvements :)
 
   
  +
one = ["one","two","three","four","five","six","seven","eight",
names = concat $
 
  +
"nine","ten","eleven","twelve","thirteen","fourteen","fifteen",
[zip [(0, n) | n <- [0..19]]
 
  +
"sixteen","seventeen","eighteen", "nineteen"]
["", "One", "Two", "Three", "Four", "Five", "Six", "Seven", "Eight"
 
,"Nine", "Ten", "Eleven", "Twelve", "Thirteen", "Fourteen", "Fifteen"
+
ty = ["twenty","thirty","forty","fifty","sixty","seventy","eighty","ninety"]
,"Sixteen", "Seventeen", "Eighteen", "Nineteen"]
 
,zip [(1, n) | n <- [0..9]]
 
["", "Ten", "Twenty", "Thirty", "Fourty", "Fifty", "Sixty", "Seventy"
 
,"Eighty", "Ninety"]
 
,[((2,0), "")]
 
,[((2, n), look (0,n) ++ " Hundred and") | n <- [1..9]]
 
,[((3,0), "")]
 
,[((3, n), look (0,n) ++ " Thousand") | n <- [1..9]]]
 
   
  +
decompose x
look n = fromJust . lookup n $ names
 
  +
| x == 0 = []
  +
| x < 20 = one !! (x-1)
  +
| x >= 20 && x < 100 =
  +
ty !! (firstDigit (x) - 2) ++ decompose ( x - firstDigit (x) * 10)
  +
| x < 1000 && x `mod` 100 ==0 =
  +
one !! (firstDigit (x)-1) ++ "hundred"
  +
| x > 100 && x <= 999 =
  +
one !! (firstDigit (x)-1) ++ "hundredand" ++decompose ( x - firstDigit (x) * 100)
  +
| x == 1000 = "onethousand"
   
  +
where firstDigit x = digitToInt . head . show $ x
spell n = unwords $ if last s == "and" then init s else s
 
where
 
s = words . unwords $ map look digs'
 
digs = reverse . zip [0..] . reverse . map digitToInt . show $ n
 
digs' = case lookup 1 digs of
 
Just 1 ->
 
let [ten,one] = filter (\(a,_) -> a<=1) digs in
 
(digs \\ [ten,one]) ++ [(0,(snd ten)*10+(snd one))]
 
otherwise -> digs
 
   
problem_17 xs = sum . map (length . filter (`notElem` " -") . spell) $ xs
+
problem_17 = length . concatMap decompose $ [1..1000]
 
</haskell>
 
</haskell>
   
Line 116: Line 191:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
problem_18 = head $ foldr1 g tri where
+
problem_18 = head $ foldr1 g tri
  +
where
 
f x y z = x + max y z
 
f x y z = x + max y z
 
g xs ys = zipWith3 f xs ys $ tail ys
 
g xs ys = zipWith3 f xs ys $ tail ys
Line 138: Line 214:
   
 
== [http://projecteuler.net/index.php?section=problems&id=19 Problem 19] ==
 
== [http://projecteuler.net/index.php?section=problems&id=19 Problem 19] ==
  +
You are given the following information, but you may prefer to do some research for yourself.
How many Sundays fell on the first of the month during the twentieth century?
 
  +
* 1 Jan 1900 was a Monday.
  +
* Thirty days has September,
  +
* April, June and November.
  +
* All the rest have thirty-one,
  +
* Saving February alone,
  +
Which has twenty-eight, rain or shine.
  +
And on leap years, twenty-nine.
  +
* A leap year occurs on any year evenly divisible by 4, but not on a century unless it is divisible by 400.
  +
  +
How many Sundays fell on the first of the month during the twentieth century
  +
(1 Jan 1901 to 31 Dec 2000)?
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
problem_19 = length . filter (== sunday) . drop 12 . take 1212 $ since1900
problem_19 = undefined
 
  +
since1900 = scanl nextMonth monday . concat $
</haskell>
 
  +
replicate 4 nonLeap ++ cycle (leap : replicate 3 nonLeap)
   
  +
nonLeap = [31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31]
== [http://projecteuler.net/index.php?section=problems&id=20 Problem 20] ==
 
Find the sum of digits in 100!
 
   
  +
leap = 31 : 29 : drop 2 nonLeap
Solution:
 
  +
<haskell>
 
  +
nextMonth x y = (x + y) `mod` 7
problem_20 = let fac n = product [1..n] in
 
  +
foldr ((+) . Data.Char.digitToInt) 0 $ show $ fac 100
 
  +
sunday = 0
  +
monday = 1
 
</haskell>
 
</haskell>
   
  +
Here is an alternative that is simpler, but it is cheating a bit:
Alternate solution, summing digits directly, which is faster than the show, digitToInt route.
 
   
 
<haskell>
 
<haskell>
  +
import Data.Time.Calendar
dsum 0 = 0
 
  +
import Data.Time.Calendar.WeekDate
dsum n = let ( d, m ) = n `divMod` 10 in m + ( dsum d )
 
   
  +
problem_19_v2 = length [() | y <- [1901..2000],
problem_20' = dsum . product $ [ 1 .. 100 ]
 
  +
m <- [1..12],
  +
let (_, _, d) = toWeekDate $ fromGregorian y m 1,
  +
d == 7]
 
</haskell>
 
</haskell>
   
  +
== [http://projecteuler.net/index.php?section=problems&id=20 Problem 20] ==
[[Category:Tutorials]]
 
  +
Find the sum of digits in 100!
[[Category:Code]]
 
  +
  +
Solution:
  +
<haskell>
  +
problem_20 = sum $ map Char.digitToInt $ show $ product [1..100]
  +
</haskell>

Latest revision as of 15:16, 16 September 2015

Problem 11

What is the greatest product of four numbers on the same straight line in the 20 by 20 grid?

Solution: using Array and Arrows, for fun :

import Control.Arrow
import Data.Array

input :: String -> Array (Int,Int) Int
input = listArray ((1,1),(20,20)) . map read . words

senses = [(+1) *** id,(+1) *** (+1), id *** (+1), (+1) *** (\n -> n - 1)]

inArray a i = inRange (bounds a) i

prods :: Array (Int, Int) Int -> [Int]
prods a = [product xs | i <- range $ bounds a,
                        s <- senses,
                        let is = take 4 $ iterate s i,
                        all (inArray a) is,
                        let xs = map (a!) is]
main = print . maximum . prods . input =<< getContents

Problem 12

What is the first triangle number to have over five-hundred divisors?

Solution:

--primeFactors in problem_3
problem_12 = head $ filter ((> 500) . nDivisors) triangleNumbers
  where nDivisors n = product $ map ((+1) . length) (group (primeFactors n))    
        triangleNumbers = scanl1 (+) [1..]

Problem 13

Find the first ten digits of the sum of one-hundred 50-digit numbers.

Solution:

main = do xs <- fmap (map read . lines) (readFile "p13.log")
          print . take 10 . show . sum $ xs

Problem 14

Find the longest sequence using a starting number under one million.

Solution:

   
import Data.List   

problem_14 = j 1000000 where   
f :: Int -> Integer -> Int   
f k 1 = k   
f k n = f (k+1) $ if even n then div n 2 else 3*n + 1   
g x y = if snd x < snd y then y else x   
h x n = g x (n, f 1 n)   
j n = fst $ foldl' h (1,1) [2..n-1]

Faster solution, using unboxed types and parallel computation:

import Control.Parallel
import Data.Word

collatzLen :: Int -> Word32 -> Int
collatzLen c 1 = c
collatzLen c n = collatzLen (c+1) $ if n `mod` 2 == 0 then n `div` 2 else 3*n+1

pmax x n = x `max` (collatzLen 1 n, n)

solve xs = foldl pmax (1,1) xs

main = print soln
    where
        s1 = solve [2..500000]
        s2 = solve [500001..1000000]
        soln = s2 `par` (s1 `pseq` max s1 s2)

Even faster solution, using an Array to memoize length of sequences :

import Data.Array
import Data.List
import Data.Ord (comparing)

syrs n = 
    a
    where 
    a = listArray (1,n) $ 0 : map syr [2..n]
    syr x = 
        if y <= n then 1 + a ! y else 1 + syr y
        where 
        y = if even x then x `div` 2 else 3 * x + 1

main = 
    print . maximumBy (comparing snd) . assocs . syrs $ 1000000


Problem 15

Starting in the top left corner in a 20 by 20 grid, how many routes are there to the bottom right corner?

Solution: A direct computation:

   
problem_15 = iterate (scanl1 (+)) (repeat 1) !! 20 !! 20

Thinking about it as a problem in combinatorics:

Each route has exactly 40 steps, with 20 of them horizontal and 20 of them vertical. We need to count how many different ways there are of choosing which steps are horizontal and which are vertical. So we have:

problem_15 = product [21..40] `div` product [2..20]

Problem 16

What is the sum of the digits of the number 21000?

Solution:

import Data.Char
problem_16 = sum k
  where s = show (2^1000)
        k = map digitToInt s

Problem 17

How many letters would be needed to write all the numbers in words from 1 to 1000?

Solution:

import Char

one = ["one","two","three","four","five","six","seven","eight",
     "nine","ten","eleven","twelve","thirteen","fourteen","fifteen",
     "sixteen","seventeen","eighteen", "nineteen"]
ty = ["twenty","thirty","forty","fifty","sixty","seventy","eighty","ninety"]

decompose x 
    | x == 0                       = []
    | x < 20                       = one !! (x-1)
    | x >= 20 && x < 100           = 
        ty !! (firstDigit (x) - 2) ++ decompose ( x - firstDigit (x) * 10)
    | x < 1000 && x `mod` 100 ==0  = 
        one !! (firstDigit (x)-1) ++ "hundred"
    | x > 100 && x <= 999          = 
        one !! (firstDigit (x)-1) ++ "hundredand" ++decompose ( x - firstDigit (x) * 100)
    | x == 1000                    = "onethousand"

  where firstDigit x = digitToInt . head . show $ x

problem_17 = length . concatMap decompose $ [1..1000]

Problem 18

Find the maximum sum travelling from the top of the triangle to the base.

Solution:

problem_18 = head $ foldr1 g tri 
  where
    f x y z = x + max y z
    g xs ys = zipWith3 f xs ys $ tail ys
    tri = [
        [75],
        [95,64],
        [17,47,82],
        [18,35,87,10],
        [20,04,82,47,65],
        [19,01,23,75,03,34],
        [88,02,77,73,07,63,67],
        [99,65,04,28,06,16,70,92],
        [41,41,26,56,83,40,80,70,33],
        [41,48,72,33,47,32,37,16,94,29],
        [53,71,44,65,25,43,91,52,97,51,14],
        [70,11,33,28,77,73,17,78,39,68,17,57],
        [91,71,52,38,17,14,91,43,58,50,27,29,48],
        [63,66,04,68,89,53,67,30,73,16,69,87,40,31],
        [04,62,98,27,23,09,70,98,73,93,38,53,60,04,23]]

Problem 19

You are given the following information, but you may prefer to do some research for yourself.

  • 1 Jan 1900 was a Monday.
  • Thirty days has September,
  • April, June and November.
  • All the rest have thirty-one,
  • Saving February alone,

Which has twenty-eight, rain or shine. And on leap years, twenty-nine.

  • A leap year occurs on any year evenly divisible by 4, but not on a century unless it is divisible by 400.

How many Sundays fell on the first of the month during the twentieth century (1 Jan 1901 to 31 Dec 2000)?

Solution:

problem_19 =  length . filter (== sunday) . drop 12 . take 1212 $ since1900
since1900 = scanl nextMonth monday . concat $
              replicate 4 nonLeap ++ cycle (leap : replicate 3 nonLeap)

nonLeap = [31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31]

leap = 31 : 29 : drop 2 nonLeap

nextMonth x y = (x + y) `mod` 7

sunday = 0
monday = 1

Here is an alternative that is simpler, but it is cheating a bit:

import Data.Time.Calendar
import Data.Time.Calendar.WeekDate

problem_19_v2 = length [() | y <- [1901..2000], 
                             m <- [1..12],
                             let (_, _, d) = toWeekDate $ fromGregorian y m 1,
                             d == 7]

Problem 20

Find the sum of digits in 100!

Solution:

problem_20 = sum $ map Char.digitToInt $ show $ product [1..100]