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

From HaskellWiki
Jump to navigation Jump to search
(Added problem_21_v2)
(→‎Problem 21: Clarify problem and add a solution.)
 
(38 intermediate revisions by 18 users not shown)
Line 1: Line 1:
  +
== [http://projecteuler.net/index.php?section=problems&id=21 Problem 21] ==
[[Category:Programming exercise spoilers]]
 
  +
Evaluate the sum of all amicable numbers (including those with a pair number over the limit) under 10000.
== [http://projecteuler.net/index.php?section=view&id=21 Problem 21] ==
 
  +
Evaluate the sum of all amicable pairs under 10000.
 
  +
Solution:
  +
(http://www.research.att.com/~njas/sequences/A063990)
   
Solution:
 
 
This is a little slow because of the naive method used to compute the divisors.
 
This is a little slow because of the naive method used to compute the divisors.
 
<haskell>
 
<haskell>
Line 16: Line 17:
 
<haskell>
 
<haskell>
 
problem_21_v2 = sum [n | n <- [2..9999], let m = d n,
 
problem_21_v2 = sum [n | n <- [2..9999], let m = d n,
m > 1, m < 10000, n == d m]
+
m > 1, m < 10000, n == d m, d m /= d (d m)]
 
d n = product [(p * product g - 1) `div` (p - 1) |
 
d n = product [(p * product g - 1) `div` (p - 1) |
 
g <- group $ primeFactors n, let p = head g
 
g <- group $ primeFactors n, let p = head g
Line 30: Line 31:
 
</haskell>
 
</haskell>
   
  +
Here is another alternative solution that computes the sum-of-divisors for the numbers by iterating over products of their factors (very fast):
== [http://projecteuler.net/index.php?section=view&id=22 Problem 22] ==
 
What is the total of all the name scores in the file of first names?
 
   
Solution:
 
 
<haskell>
 
<haskell>
  +
import Data.Array
-- apply to a list of names
 
problem_22 :: [String] -> Int
 
problem_22 = sum . zipWith (*) [ 1 .. ] . map score
 
where score = sum . map ( subtract 64 . ord )
 
</haskell>
 
   
  +
max_ = 100000
== [http://projecteuler.net/index.php?section=view&id=23 Problem 23] ==
 
Find the sum of all the positive integers which cannot be written as the sum of two abundant numbers.
 
   
  +
gen 100001 = []
Solution:
 
  +
gen n = [(i*n,n)|i <- [2 .. max_ `div` n]] ++ (gen (n+1))
<haskell>
 
import Data.Set hiding (filter, map)
 
import Data.List (scanl, group)
 
   
  +
arr = accumArray (+) 0 (0,max_) (gen 1)
problem_23 :: Integer
 
problem_23 = sum [1..28123] - (fold (+) 0 $ abundant_sums $ abundant 28123)
 
   
  +
problem_21_v3 = sum $ filter (\a -> let b = (arr!a) in b /= a && (arr!b) == a) [1 .. (10000 - 1)]
abundant_sums :: [Integer] -> Set Integer
 
abundant_sums [] = empty
 
abundant_sums l@(x:xs) = union (fromList [x + a | a <- takeWhile (\y -> y <= 28123 - x) l]) (abundant_sums xs)
 
   
abundant :: Integer -> [Integer]
 
abundant n = [a | a <- [1..n], (sum $ factors a) - a > a]
 
 
primes :: [Integer]
 
primes = 2 : filter ((==1) . length . primeFactors) [3,5..]
 
 
primeFactors :: Integer -> [Integer]
 
primeFactors n = factor n primes
 
where
 
factor _ [] = []
 
factor m (p:ps) | p*p > m = [m]
 
| m `mod` p == 0 = p : factor (m `div` p) (p:ps)
 
| otherwise = factor m ps
 
 
factors :: Integer -> [Integer]
 
factors = perms . map (tail . scanl (*) 1) . group . primeFactors
 
where
 
perms :: (Integral a) => [[a]] -> [a]
 
perms [] = [1]
 
perms (x:xs) = perms xs ++ concatMap (\z -> map (*z) $ perms xs) x
 
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=24 Problem 24] ==
+
== [http://projecteuler.net/index.php?section=problems&id=22 Problem 22] ==
What is the millionth lexicographic permutation of the digits 0, 1, 2, 3, 4, 5, 6, 7, 8 and 9?
+
What is the total of all the name scores in the file of first names?
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import Data.List
perms [] = [[]]
 
  +
import Data.Char
perms xs = do
 
  +
problem_22 =
x <- xs
 
  +
do input <- readFile "names.txt"
map ( x: ) ( perms . delete x $ xs )
 
  +
let names = sort $ read$"["++ input++"]"
 
  +
let scores = zipWith score names [1..]
problem_24 = ( perms "0123456789" ) !! 999999
 
  +
print . sum $ scores
  +
where score w i = (i *) . sum . map (\c -> ord c - ord 'A' + 1) $ w
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=25 Problem 25] ==
+
== [http://projecteuler.net/index.php?section=problems&id=23 Problem 23] ==
  +
Find the sum of all the positive integers which cannot be written as the sum of two abundant numbers.
What is the first term in the Fibonacci sequence to contain 1000 digits?
 
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
--http://www.research.att.com/~njas/sequences/A048242
valid ( i, n ) = length ( show n ) == 1000
 
  +
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
problem_25 = fst . head . filter valid . zip [ 1 .. ] $ fibs
 
  +
isSum = any (abunds_array !) . rests
where fibs = 1 : 1 : 2 : zipWith (+) fibs ( tail fibs )
 
  +
  +
problem_23 = print . sum . filter (not . isSum) $ [1..n]
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=26 Problem 26] ==
+
== [http://projecteuler.net/index.php?section=problems&id=24 Problem 24] ==
  +
What is the millionth lexicographic permutation of the digits 0, 1, 2, 3, 4, 5, 6, 7, 8 and 9?
Find the value of d < 1000 for which 1/d contains the longest recurring cycle.
 
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import Data.List
problem_26 = fst $ maximumBy (\a b -> snd a `compare` snd b)
 
  +
[(n,recurringCycle n) | n <- [1..999]]
 
  +
fac 0 = 1
where recurringCycle d = remainders d 10 []
 
  +
fac n = n * fac (n - 1)
remainders d 0 rs = 0
 
  +
perms [] _= []
remainders d r rs = let r' = r `mod` d
 
  +
perms xs n= x : perms (delete x xs) (mod n m)
in case findIndex (== r') rs of
 
  +
where m = fac $ length xs - 1
Just i -> i + 1
 
  +
y = div n m
Nothing -> remainders d (10*r') (r':rs)
 
  +
x = xs!!y
  +
  +
problem_24 = perms "0123456789" 999999
 
</haskell>
 
</haskell>
   
  +
Or, using Data.List.permutations,
== [http://projecteuler.net/index.php?section=view&id=27 Problem 27] ==
 
  +
<haskell>
Find a quadratic formula that produces the maximum number of primes for consecutive values of n.
 
  +
import Data.List
  +
problem_24 = (!! 999999) . sort $ permutations ['0'..'9']
  +
</haskell>
   
  +
Casey Hawthorne
Solution:
 
   
  +
For Project Euler #24 you don't need to generate all the lexicographic permutations by Knuth's method or any other.
The following is written in [http://haskell.org/haskellwiki/Literate_programming#Haskell_and_literate_programming literate Haskell]:
 
<haskell>
 
> import Data.List
 
   
  +
You're only looking for the millionth lexicographic permutation of "0123456789"
To be sure we get the maximum type checking of the compiler,
 
we switch off the default type
 
   
  +
<haskell>
> default ()
 
   
Generate a list of primes.
+
-- Plan of attack.
It works by filtering out numbers that are
 
divisable by a previously found prime
 
   
  +
-- The "x"s are different numbers
> primes :: [Int]
 
  +
-- 0xxxxxxxxx represents 9! = 362880 permutations/numbers
> primes = sieve (2 : [3, 5..])
 
  +
-- 1xxxxxxxxx represents 9! = 362880 permutations/numbers
> where
 
  +
-- 2xxxxxxxxx represents 9! = 362880 permutations/numbers
> sieve (p:xs) = p : sieve (filter (\x -> x `mod` p > 0) xs)
 
   
> isPrime :: Int -> Bool
 
> isPrime x = x `elem` (takeWhile (<= x) primes)
 
   
  +
-- 20xxxxxxxx represents 8! = 40320
  +
-- 21xxxxxxxx represents 8! = 40320
   
  +
-- 23xxxxxxxx represents 8! = 40320
The lists of values we are going to try for a and b;
 
  +
-- 24xxxxxxxx represents 8! = 40320
b must be a prime, as n² + an + b is equal to b when n = 0
 
  +
-- 25xxxxxxxx represents 8! = 40320
  +
-- 26xxxxxxxx represents 8! = 40320
  +
-- 27xxxxxxxx represents 8! = 40320
   
> testRangeA :: [Int]
 
> testRangeA = [-1000 .. 1000]
 
   
  +
module Euler where
> testRangeB :: [Int]
 
> testRangeB = takeWhile (< 1000) primes
 
   
  +
import Data.List
   
  +
factorial n = product [1..n]
The search
 
   
  +
-- lexOrder "0123456789" 1000000 ""
> bestCoefficients :: (Int, Int, Int)
 
> bestCoefficients =
 
> maximumBy (\(x, _, _) (y, _, _) -> compare x y) $
 
> [f a b | a <- testRangeA, b <- testRangeB]
 
> where
 
   
  +
lexOrder digits left s
Generate a list of results of the quadratic formula
 
  +
| len == 0 = s ++ digits
(only the contiguous primes)
 
  +
| quot > 0 && rem == 0 = lexOrder (digits\\(show (digits!!(quot-1)))) rem (s ++ [(digits!!(quot-1))])
wrap the result in a triple, together with a and b
 
  +
| 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>
> f :: Int -> Int -> (Int, Int, Int)
 
> f a b = ( length $ contiguousPrimes a b
 
> , a
 
> , b
 
> )
 
   
  +
== [http://projecteuler.net/index.php?section=problems&id=25 Problem 25] ==
> contiguousPrimes :: Int -> Int -> [Int]
 
  +
What is the first term in the Fibonacci sequence to contain 1000 digits?
> contiguousPrimes a b = takeWhile isPrime (map (quadratic a b) [0..])
 
   
  +
Solution:
  +
<haskell>
  +
fibs = 0:1:(zipWith (+) fibs (tail fibs))
  +
t = 10^999
   
  +
problem_25 = length w
The quadratic formula
 
  +
where
  +
w = takeWhile (< t) fibs
  +
</haskell>
   
> quadratic :: Int -> Int -> Int -> Int
 
> quadratic a b n = n * n + a * n + b
 
   
  +
Casey Hawthorne
   
  +
I believe you mean the following:
> problem_27 =
 
> do
 
> let (l, a, b) = bestCoefficients
 
>
 
> putStrLn $ ""
 
> putStrLn $ "Problem Euler 27"
 
> putStrLn $ ""
 
> putStrLn $ "The best quadratic formula found is:"
 
> putStrLn $ " n * n + " ++ show a ++ " * n + " ++ show b
 
> putStrLn $ ""
 
> putStrLn $ "The number of primes is: " ++ (show l)
 
> putStrLn $ ""
 
> putStrLn $ "The primes are:"
 
> print $ take l $ contiguousPrimes a b
 
> putStrLn $ ""
 
   
  +
<haskell>
   
  +
fibs = 0:1:(zipWith (+) fibs (tail fibs))
  +
  +
last (takeWhile (<10^1000) fibs)
 
</haskell>
 
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=28 Problem 28] ==
+
== [http://projecteuler.net/index.php?section=problems&id=26 Problem 26] ==
  +
Find the value of d < 1000 for which 1/d contains the longest recurring cycle.
What is the sum of both diagonals in a 1001 by 1001 spiral?
 
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
problem_26 = fst $ maximumBy (comparing snd)
corners :: Int -> (Int, Int, Int, Int)
 
  +
[(n,recurringCycle n) | n <- [1..999]]
corners i = (n*n, 1+(n*(2*m)), 2+(n*(2*m-1)), 3+(n*(2*m-2)))
 
where m = (i-1) `div` 2
+
where recurringCycle d = remainders d 10 []
n = 2*m+1
+
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>
   
  +
== [http://projecteuler.net/index.php?section=problems&id=27 Problem 27] ==
sumcorners :: Int -> Int
 
  +
Find a quadratic formula that produces the maximum number of primes for consecutive values of n.
sumcorners i = a+b+c+d where (a, b, c, d) = corners i
 
   
  +
Solution:
sumdiags :: Int -> Int
 
  +
<haskell>
sumdiags i | even i = error "not a spiral"
 
  +
problem_27 = -(2*a-1)*(a^2-a+41)
| i == 3 = s + 1
 
  +
where n = 1000
| otherwise = s + sumdiags (i-2)
 
where s = sumcorners i
+
m = head $ filter (\x->x^2-x+41>n) [1..]
  +
a = m-1
  +
</haskell>
   
  +
== [http://projecteuler.net/index.php?section=problems&id=28 Problem 28] ==
problem_28 = sumdiags 1001
 
  +
What is the sum of both diagonals in a 1001 by 1001 spiral?
  +
  +
Solution:
  +
<haskell>
  +
problem_28 = sum (map (\n -> 4*(n-2)^2+10*(n-1)) [3,5..1001]) + 1
 
</haskell>
 
</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:
You can note that from 1 to 3 there's (+2), and such too for 5, 7 and 9, it then goes up to (+4) 4 times, and so on, adding 2 to the number to add for each level of the spiral. You can so avoid all need for multiplications and just do additions with the following code :
 
  +
<haskell>problem_28 = sum . scanl (+) 1 . concatMap (replicate 4) $ [2,4..1000]</haskell>
 
  +
<haskell>
  +
euler28 n = sum $ scanl (+) 0
  +
(1:(concatMap (replicate 4) [2,4..(n-1)]))
  +
</haskell>
   
== [http://projecteuler.net/index.php?section=view&id=29 Problem 29] ==
+
== [http://projecteuler.net/index.php?section=problems&id=29 Problem 29] ==
 
How many distinct terms are in the sequence generated by a<sup>b</sup> for 2 ≤ a ≤ 100 and 2 ≤ b ≤ 100?
 
How many distinct terms are in the sequence generated by a<sup>b</sup> for 2 ≤ a ≤ 100 and 2 ≤ b ≤ 100?
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import Control.Monad
problem_29 = length . group . sort $ [a^b | a <- [2..100], b <- [2..100]]
 
  +
problem_29 = length . group . sort $ liftM2 (^) [2..100] [2..100]
 
</haskell>
 
</haskell>
   
  +
We can also solve it in a more naive way, without using Monads, like this:
== [http://projecteuler.net/index.php?section=view&id=30 Problem 30] ==
 
  +
<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>
  +
  +
== [http://projecteuler.net/index.php?section=problems&id=30 Problem 30] ==
 
Find the sum of all the numbers that can be written as the sum of fifth powers of their digits.
 
Find the sum of all the numbers that can be written as the sum of fifth powers of their digits.
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
import Data.Char (ord)
+
import Data.Char (digitToInt)
   
 
limit :: Integer
 
limit :: Integer
Line 245: Line 259:
   
 
fifth :: Integer -> Integer
 
fifth :: Integer -> Integer
fifth n = foldr (\a b -> (toInteger(ord a) - 48)^5 + b) 0 $ show n
+
fifth = sum . map ((^5) . toInteger . digitToInt) . show
   
 
problem_30 :: Integer
 
problem_30 :: Integer
 
problem_30 = sum $ filter (\n -> n == fifth n) [2..limit]
 
problem_30 = sum $ filter (\n -> n == fifth n) [2..limit]
 
</haskell>
 
</haskell>
 
 
[[Category:Tutorials]]
 
[[Category:Code]]
 

Latest revision as of 15:53, 11 October 2015

Problem 21

Evaluate the sum of all amicable numbers (including those with a pair number over the limit) 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..]

Here is another alternative solution that computes the sum-of-divisors for the numbers by iterating over products of their factors (very fast):

import Data.Array

max_ = 100000

gen 100001 = []
gen n = [(i*n,n)|i <- [2 .. max_ `div` n]] ++ (gen (n+1))

arr = accumArray (+) 0 (0,max_) (gen 1)

problem_21_v3 = sum $ filter (\a -> let b = (arr!a) in b /= a && (arr!b) == a) [1 .. (10000 - 1)]

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]