Euler problems/21 to 30: Difference between revisions
No edit summary |
CaleGibbard (talk | contribs) No edit summary |
||
Line 15: | Line 15: | ||
import Data.List | import Data.List | ||
import Data.Char | import Data.Char | ||
problem_22 = | problem_22 = | ||
input <- readFile "names.txt" | do input <- readFile "names.txt" | ||
let names = sort $ read$"["++ input++"]" | |||
let scores = zipWith score names [1..] | |||
print . show . sum $ scores | |||
where score w i = (i *) . sum . map (\c -> ord c - ord 'A' + 1) $ w | |||
</haskell> | </haskell> | ||
Line 39: | Line 38: | ||
isSum = any (abunds_array !) . rests | isSum = any (abunds_array !) . rests | ||
problem_23 = putStrLn | problem_23 = putStrLn . show . foldl1 (+) . filter (not . isSum) $ [1..n] | ||
</haskell> | </haskell> | ||
Line 52: | Line 51: | ||
fac n = n * fac (n - 1) | fac n = n * fac (n - 1) | ||
perms [] _= [] | perms [] _= [] | ||
perms xs n= | 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 = | problem_24 = perms "0123456789" 999999 | ||
</haskell> | </haskell> | ||
Line 69: | Line 66: | ||
import Data.List | import Data.List | ||
fib x | fib x | ||
| x==0 = 0 | |||
| x==1 = 1 | |||
| odd x = (fib (d+1))^2 + (fib d)^2 | |||
| otherwise = (fib (d+1))^2-(fib (d-1))^2 | |||
where d = x `div` 2 | |||
phi=(1+sqrt 5)/2 | phi = (1+sqrt 5)/2 | ||
dig x=floor( (fromInteger x-1) * log 10 /log phi) | |||
problem_25 = | dig x = floor ((fromInteger x-1) * log 10 / log phi) | ||
problem_25 = head [a | a<-[dig num..], fib a >= limit] | |||
where num = 1000 | |||
limit = 10^(num-1) | |||
</haskell> | </haskell> | ||
Line 91: | Line 86: | ||
Solution: | Solution: | ||
<haskell> | <haskell> | ||
problem_26 = head [a|a<-[999,997..], | problem_26 = head [a | a<-[999,997..], and [isPrime a, isPrime $ a `div` 2]] | ||
</haskell> | </haskell> | ||
Line 99: | Line 94: | ||
Solution: | Solution: | ||
<haskell> | <haskell> | ||
problem_27= | 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 | |||
</haskell> | </haskell> | ||
Revision as of 19:25, 19 February 2008
Problem 21
Evaluate the sum of all amicable pairs under 10000.
Solution:
--http://www.research.att.com/~njas/sequences/A063990
problem_21 = sum [220, 284, 1184, 1210, 2620, 2924, 5020, 5564, 6232, 6368]
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 . show . 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 = putStrLn . show . foldl1 (+) . 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
Problem 25
What is the first term in the Fibonacci sequence to contain 1000 digits?
Solution:
import Data.List
fib x
| x==0 = 0
| x==1 = 1
| odd x = (fib (d+1))^2 + (fib d)^2
| otherwise = (fib (d+1))^2-(fib (d-1))^2
where d = x `div` 2
phi = (1+sqrt 5)/2
dig x = floor ((fromInteger x-1) * log 10 / log phi)
problem_25 = head [a | a<-[dig num..], fib a >= limit]
where num = 1000
limit = 10^(num-1)
Problem 26
Find the value of d < 1000 for which 1/d contains the longest recurring cycle.
Solution:
problem_26 = head [a | a<-[999,997..], and [isPrime a, isPrime $ a `div` 2]]
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
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]
Problem 30
Find the sum of all the numbers that can be written as the sum of fifth powers of their digits.
Solution:
--http://www.research.att.com/~njas/sequences/A052464
problem_30 = sum [4150, 4151, 54748, 92727, 93084, 194979]