Difference between revisions of "Euler problems/21 to 30"

From HaskellWiki
Jump to navigation Jump to search
(remove comment which didn't apply to the solution given. If you want to improve the solutions, do what HenryLaxen is doing, and actually improve them.)
(→‎Problem 24: Added another method for Problem 24)
(20 intermediate revisions by 10 users not shown)
Line 2: Line 2:
 
Evaluate the sum of all amicable pairs under 10000.
 
Evaluate the sum of all amicable pairs under 10000.
   
  +
Solution:
  +
(http://www.research.att.com/~njas/sequences/A063990)
  +
  +
This is a little slow because of the naive method used to compute the divisors.
  +
<haskell>
  +
problem_21 = sum [m+n | m <- [2..9999], let n = divisorsSum ! m, amicable m n]
  +
where amicable m n = m < n && n < 10000 && divisorsSum ! n == m
  +
divisorsSum = array (1,9999)
  +
[(i, sum (divisors i)) | i <- [1..9999]]
  +
divisors n = [j | j <- [1..n `div` 2], n `mod` j == 0]
  +
</haskell>
  +
  +
Here is an alternative using a faster way of computing the sum of divisors.
 
<haskell>
 
<haskell>
  +
problem_21_v2 = sum [n | n <- [2..9999], let m = d n,
--http://www.research.att.com/~njas/sequences/A063990
 
  +
m > 1, m < 10000, n == d m, d m /= d (d m)]
problem_21 = sum [220, 284, 1184, 1210, 2620, 2924, 5020, 5564, 6232, 6368]
 
  +
d n = product [(p * product g - 1) `div` (p - 1) |
  +
g <- group $ primeFactors n, let p = head g
  +
] - n
  +
primeFactors = pf primes
  +
where
  +
pf ps@(p:ps') n
  +
| p * p > n = [n]
  +
| r == 0 = p : pf ps q
  +
| otherwise = pf ps' n
  +
where (q, r) = n `divMod` p
  +
primes = 2 : filter (null . tail . primeFactors) [3,5..]
 
</haskell>
 
</haskell>
   
Line 18: Line 42:
 
let names = sort $ read$"["++ input++"]"
 
let names = sort $ read$"["++ input++"]"
 
let scores = zipWith score names [1..]
 
let scores = zipWith score names [1..]
print . show . sum $ scores
+
print . sum $ scores
 
where score w i = (i *) . sum . map (\c -> ord c - ord 'A' + 1) $ w
 
where score w i = (i *) . sum . map (\c -> ord c - ord 'A' + 1) $ w
 
</haskell>
 
</haskell>
Line 37: Line 61:
 
isSum = any (abunds_array !) . rests
 
isSum = any (abunds_array !) . rests
   
problem_23 = putStrLn . show . foldl1 (+) . filter (not . isSum) $ [1..n]
+
problem_23 = print . sum . filter (not . isSum) $ [1..n]
 
</haskell>
 
</haskell>
   
Line 56: Line 80:
 
 
 
problem_24 = perms "0123456789" 999999
 
problem_24 = perms "0123456789" 999999
  +
</haskell>
  +
  +
Or, using Data.List.permutations,
  +
<haskell>
  +
import Data.List
  +
problem_24 = (!! 999999) . sort $ permutations ['0'..'9']
  +
</haskell>
  +
  +
Casey Hawthorne
  +
  +
For Project Euler #24 you don't need to generate all the lexicographic permutations by Knuth's method or any other.
  +
  +
You're only looking for the millionth lexicographic permutation of "0123456789"
  +
  +
<haskell>
  +
  +
-- Plan of attack.
  +
  +
-- The "x"s are different numbers
  +
-- 0xxxxxxxxx represents 9! = 362880 permutations/numbers
  +
-- 1xxxxxxxxx represents 9! = 362880 permutations/numbers
  +
-- 2xxxxxxxxx represents 9! = 362880 permutations/numbers
  +
  +
  +
-- 20xxxxxxxx represents 8! = 40320
  +
-- 21xxxxxxxx represents 8! = 40320
  +
  +
-- 23xxxxxxxx represents 8! = 40320
  +
-- 24xxxxxxxx represents 8! = 40320
  +
-- 25xxxxxxxx represents 8! = 40320
  +
-- 26xxxxxxxx represents 8! = 40320
  +
-- 27xxxxxxxx represents 8! = 40320
  +
  +
  +
module Euler where
  +
  +
import Data.List
  +
  +
factorial n = product [1..n]
  +
  +
-- lexOrder "0123456789" 1000000 ""
  +
  +
lexOrder digits left s
  +
| len == 0 = s ++ digits
  +
| quot > 0 && rem == 0 = lexOrder (digits\\(show (digits!!(quot-1)))) rem (s ++ [(digits!!(quot-1))])
  +
| quot == 0 && rem == 0 = lexOrder (digits\\(show (digits!!len))) rem (s ++ [(digits!!len)])
  +
| rem == 0 = lexOrder (digits\\(show (digits!!(quot+1)))) rem (s ++ [(digits!!(quot+1))])
  +
| otherwise = lexOrder (digits\\(show (digits!!(quot)))) rem (s ++ [(digits!!(quot))])
  +
where
  +
len = (length digits) - 1
  +
(quot,rem) = quotRem left (factorial len)
  +
 
</haskell>
 
</haskell>
   
Line 63: Line 139:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
fibs = 0:1:(zipWith (+) fibs (tail fibs))
valid ( i, n ) = length ( show n ) == 1000
 
  +
t = 10^999
 
  +
problem_25 = fst . head . filter valid . zip [ 1 .. ] $ fibs
 
  +
problem_25 = length w
where fibs = 1 : 1 : 2 : zipWith (+) fibs ( tail fibs )
 
  +
where
  +
w = takeWhile (< t) fibs
  +
</haskell>
  +
  +
  +
Casey Hawthorne
  +
  +
I believe you mean the following:
  +
  +
<haskell>
  +
  +
fibs = 0:1:(zipWith (+) fibs (tail fibs))
  +
  +
last (takeWhile (<10^1000) fibs)
 
</haskell>
 
</haskell>
   
Line 74: Line 164:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
problem_26 = fst $ maximumBy (comparing snd)
problem_26 = head [a | a<-[999,997..], and [isPrime a, isPrime $ a `div` 2]]
 
  +
[(n,recurringCycle n) | n <- [1..999]]
  +
where recurringCycle d = remainders d 10 []
  +
remainders d 0 rs = 0
  +
remainders d r rs = let r' = r `mod` d
  +
in case elemIndex r' rs of
  +
Just i -> i + 1
  +
Nothing -> remainders d (10*r') (r':rs)
 
</haskell>
 
</haskell>
   
Line 94: Line 191:
 
<haskell>
 
<haskell>
 
problem_28 = sum (map (\n -> 4*(n-2)^2+10*(n-1)) [3,5..1001]) + 1
 
problem_28 = sum (map (\n -> 4*(n-2)^2+10*(n-1)) [3,5..1001]) + 1
  +
</haskell>
  +
  +
Alternatively, one can use the fact that the distance between the diagonal numbers increases by 2 in every concentric square. Each square contains four gaps, so the following <hask>scanl</hask> does the trick:
  +
  +
<haskell>
  +
euler28 n = sum $ scanl (+) 0
  +
(1:(concatMap (replicate 4) [2,4..(n-1)]))
 
</haskell>
 
</haskell>
   
Line 103: Line 207:
 
import Control.Monad
 
import Control.Monad
 
problem_29 = length . group . sort $ liftM2 (^) [2..100] [2..100]
 
problem_29 = length . group . sort $ liftM2 (^) [2..100] [2..100]
  +
</haskell>
  +
  +
We can also solve it in a more naive way, without using Monads, like this:
  +
<haskell>
  +
import List
  +
problem_29 = length $ nub pr29_help
  +
where pr29_help = [z | y <- [2..100],
  +
z <- lift y]
  +
lift y = map (\x -> x^y) [2..100]
  +
</haskell>
  +
  +
Simpler:
  +
  +
<haskell>
  +
import List
  +
problem_29 = length $ nub [x^y | x <- [2..100], y <- [2..100]]
  +
</haskell>
  +
  +
Instead of using lists, the Set data structure can be used for a significant speed increase:
  +
  +
<haskell>
  +
import Set
  +
problem_29 = size $ fromList [x^y | x <- [2..100], y <- [2..100]]
 
</haskell>
 
</haskell>
   
Line 110: Line 237:
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import Data.Char (digitToInt)
--http://www.research.att.com/~njas/sequences/A052464
 
problem_30 = sum [4150, 4151, 54748, 92727, 93084, 194979]
 
</haskell>
 
   
  +
limit :: Integer
I'm sorry, but I find the solution to problem 30 very unsatisfying. I'm using the Euler problems to learn Haskell, so looking up the answer and adding the terms isn't really that helpful. I would like to present the following as a clearer solution that perhaps gives a little more insight into the problem and programming in Haskell. -- Henry Laxen, Feb 20, 2008
 
  +
limit = snd $ head $ dropWhile (\(a,b) -> a > b) $ zip (map (9^5*) [1..]) (map (10^) [1..])
   
  +
fifth :: Integer -> Integer
  +
fifth = sum . map ((^5) . toInteger . digitToInt) . show
   
  +
problem_30 :: Integer
<haskell>
 
problem_30 = sum $ map listToInt (drop 2 ans)
+
problem_30 = sum $ filter (\n -> n == fifth n) [2..limit]
-- we drop 2 because the first two members of the ans are 0 and 1,
 
-- which are considered "trivial" solutions and should not count in the sum
 
where maxFirstDigit = (6*9^5 `div` 10^5) + 1
 
-- The largest number that can be the sum of fifth powers
 
-- is 6*9^5 = 354294, which has 6 digits
 
listToInt n = foldl (\x y -> 10*x+y) 0 n
 
isSumOfPowers p n = (sum $ map (\x -> x^p) n) == listToInt n
 
ans = filter (isSumOfPowers 5) [ [a,b,c,d,e,f] |
 
a <- [0..maxFirstDigit],
 
b <- [0..9],
 
c <- [0..9],
 
d <- [0..9],
 
e <- [0..9],
 
f <- [0..9] ]
 
 
</haskell>
 
</haskell>

Revision as of 03:52, 14 November 2011

Problem 21

Evaluate the sum of all amicable pairs under 10000.

Solution: (http://www.research.att.com/~njas/sequences/A063990)

This is a little slow because of the naive method used to compute the divisors.

problem_21 = sum [m+n | m <- [2..9999], let n = divisorsSum ! m, amicable m n]
    where amicable m n = m < n && n < 10000 && divisorsSum ! n == m
          divisorsSum = array (1,9999)
                        [(i, sum (divisors i)) | i <- [1..9999]]
          divisors n = [j | j <- [1..n `div` 2], n `mod` j == 0]

Here is an alternative using a faster way of computing the sum of divisors.

problem_21_v2 = sum [n | n <- [2..9999], let m = d n,
                         m > 1, m < 10000, n == d m, d m /= d  (d m)]
d n = product [(p * product g - 1) `div` (p - 1) |
                 g <- group $ primeFactors n, let p = head g
              ] - n
primeFactors = pf primes
  where
    pf ps@(p:ps') n
     | p * p > n = [n]
     | r == 0    = p : pf ps q
     | otherwise = pf ps' n
     where (q, r) = n `divMod` p
primes = 2 : filter (null . tail . primeFactors) [3,5..]

Problem 22

What is the total of all the name scores in the file of first names?

Solution:

import Data.List
import Data.Char
problem_22 =
    do input <- readFile "names.txt"
       let names = sort $ read$"["++ input++"]"
       let scores = zipWith score names [1..]
       print . sum $ scores
  where score w i = (i *) . sum . map (\c -> ord c - ord 'A' + 1) $ w

Problem 23

Find the sum of all the positive integers which cannot be written as the sum of two abundant numbers.

Solution:

--http://www.research.att.com/~njas/sequences/A048242
import Data.Array 
n = 28124
abundant n = eulerTotient n - n > n
abunds_array = listArray (1,n) $ map abundant [1..n]
abunds = filter (abunds_array !) [1..n]

rests x = map (x-) $ takeWhile (<= x `div` 2) abunds
isSum = any (abunds_array !) . rests

problem_23 = print . sum . filter (not . isSum) $ [1..n]

Problem 24

What is the millionth lexicographic permutation of the digits 0, 1, 2, 3, 4, 5, 6, 7, 8 and 9?

Solution:

import Data.List 
 
fac 0 = 1
fac n = n * fac (n - 1)
perms [] _= []
perms xs n= x : perms (delete x xs) (mod n m)
  where m = fac $ length xs - 1
        y = div n m
        x = xs!!y
 
problem_24 = perms "0123456789" 999999

Or, using Data.List.permutations,

import Data.List
problem_24 = (!! 999999) . sort $ permutations ['0'..'9']

Casey Hawthorne

For Project Euler #24 you don't need to generate all the lexicographic permutations by Knuth's method or any other.

You're only looking for the millionth lexicographic permutation of "0123456789"

-- Plan of attack.

-- The "x"s are different numbers
-- 0xxxxxxxxx represents 9! = 362880 permutations/numbers
-- 1xxxxxxxxx represents 9! = 362880 permutations/numbers
-- 2xxxxxxxxx represents 9! = 362880 permutations/numbers


-- 20xxxxxxxx represents 8! = 40320
-- 21xxxxxxxx represents 8! = 40320

-- 23xxxxxxxx represents 8! = 40320
-- 24xxxxxxxx represents 8! = 40320
-- 25xxxxxxxx represents 8! = 40320
-- 26xxxxxxxx represents 8! = 40320
-- 27xxxxxxxx represents 8! = 40320


module Euler where

import Data.List

factorial n = product [1..n]

-- lexOrder "0123456789" 1000000 ""

lexOrder digits left s
    | len == 0              = s ++ digits
    | quot > 0 && rem == 0  = lexOrder (digits\\(show (digits!!(quot-1))))  rem (s ++ [(digits!!(quot-1))])
    | quot == 0 && rem == 0 = lexOrder (digits\\(show (digits!!len)))       rem (s ++ [(digits!!len)])
    | rem == 0              = lexOrder (digits\\(show (digits!!(quot+1))))  rem (s ++ [(digits!!(quot+1))])
    | otherwise             = lexOrder (digits\\(show (digits!!(quot))))    rem (s ++ [(digits!!(quot))])
    where
    len = (length digits) - 1
    (quot,rem) = quotRem left (factorial len)

Problem 25

What is the first term in the Fibonacci sequence to contain 1000 digits?

Solution:

fibs = 0:1:(zipWith (+) fibs (tail fibs))
t = 10^999

problem_25 = length w
    where
      w = takeWhile (< t) fibs


Casey Hawthorne

I believe you mean the following:

fibs = 0:1:(zipWith (+) fibs (tail fibs))

last (takeWhile (<10^1000) fibs)

Problem 26

Find the value of d < 1000 for which 1/d contains the longest recurring cycle.

Solution:

problem_26 = fst $ maximumBy (comparing snd)
                            [(n,recurringCycle n) | n <- [1..999]]
    where  recurringCycle d = remainders d 10 []
           remainders d 0 rs = 0
           remainders d r rs = let r' = r `mod` d
                               in case elemIndex r' rs of
                                    Just i  -> i + 1
                                    Nothing -> remainders d (10*r') (r':rs)

Problem 27

Find a quadratic formula that produces the maximum number of primes for consecutive values of n.

Solution:

problem_27 = -(2*a-1)*(a^2-a+41)
  where n = 1000
        m = head $ filter (\x->x^2-x+41>n) [1..]
        a = m-1

Problem 28

What is the sum of both diagonals in a 1001 by 1001 spiral?

Solution:

problem_28 = sum (map (\n -> 4*(n-2)^2+10*(n-1)) [3,5..1001]) + 1

Alternatively, one can use the fact that the distance between the diagonal numbers increases by 2 in every concentric square. Each square contains four gaps, so the following scanl does the trick:

euler28 n = sum $ scanl (+) 0
            (1:(concatMap (replicate 4) [2,4..(n-1)]))

Problem 29

How many distinct terms are in the sequence generated by ab for 2 ≤ a ≤ 100 and 2 ≤ b ≤ 100?

Solution:

import Control.Monad
problem_29 = length . group . sort $ liftM2 (^) [2..100] [2..100]

We can also solve it in a more naive way, without using Monads, like this:

import List
problem_29 = length $ nub pr29_help
    where pr29_help  = [z | y <- [2..100],
                        z <- lift y]
          lift y = map (\x -> x^y) [2..100]

Simpler:

import List
problem_29 = length $ nub [x^y | x <- [2..100], y <- [2..100]]

Instead of using lists, the Set data structure can be used for a significant speed increase:

import Set
problem_29 = size $ fromList [x^y | x <- [2..100], y <- [2..100]]

Problem 30

Find the sum of all the numbers that can be written as the sum of fifth powers of their digits.

Solution:

import Data.Char (digitToInt)

limit :: Integer
limit = snd $ head $ dropWhile (\(a,b) -> a > b) $ zip (map (9^5*) [1..]) (map (10^) [1..])

fifth :: Integer -> Integer
fifth = sum . map ((^5) . toInteger . digitToInt) . show

problem_30 :: Integer
problem_30 = sum $ filter (\n -> n == fifth n) [2..limit]