Difference between revisions of "Euler problems/151 to 160"

From HaskellWiki
Jump to navigation Jump to search
 
(Added problem_152)
Line 10: Line 10:
 
== [http://projecteuler.net/index.php?section=view&id=152 Problem 152] ==
 
== [http://projecteuler.net/index.php?section=view&id=152 Problem 152] ==
 
Writing 1/2 as a sum of inverse squares
 
Writing 1/2 as a sum of inverse squares
  +
  +
Note that if p is an odd prime, the sum of inverse squares of
  +
all terms divisible by p must have reduced denominator not divisible
  +
by p.
   
 
Solution:
 
Solution:
 
<haskell>
 
<haskell>
  +
import Data.Ratio
problem_152 = undefined
 
  +
import Data.List
  +
  +
invSq n = 1 % (n * n)
  +
sumInvSq = sum . map invSq
  +
  +
subsets (x:xs) = let s = subsets xs in s ++ map (x :) s
  +
subsets _ = [[]]
  +
  +
primes = 2 : 3 : 7 : [p | p <- [11, 13..83],
  +
all (\q -> p `mod` q /= 0) [3, 5, 7]]
  +
  +
-- All subsets whose sum of inverse squares,
  +
-- when added to x, does not contain a factor of p
  +
pfree s x p = [(y, t) | t <- subsets s, let y = x + sumInvSq t,
  +
denominator y `mod` p /= 0]
  +
  +
-- Verify that we need not consider terms divisible by 11, or by any
  +
-- prime greater than 13. Nor need we consider any term divisible
  +
-- by 25, 27, 32, or 49.
  +
verify = all (\p -> null $ tail $ pfree [p, 2*p..85] 0 p) $
  +
11 : dropWhile (< 17) primes ++ [25, 27, 32, 49]
  +
  +
-- All pairs (x, n) where x is a rational number whose reduced
  +
-- denominator is not divisible by any prime greater than 3;
  +
-- and n>0 is the number of sets of numbers up to 85 divisible
  +
-- by a prime greater than 3, whose sum of inverse squares is x.
  +
only23 = foldl f [(0, 1)] [13, 7, 5]
  +
where
  +
f x p = collect $ concatMap (g p) x
  +
g p (x, n) = map (\(a, b) -> (a, n * length b)) $ pfree (terms p) x p
  +
terms p = [n * p | n <- [1..85`div`p],
  +
all (\q -> n `mod` q /= 0) [5, 7, 11, 13, 17]]
  +
collect = map (\z -> (fst $ head z, sum $ map snd z))
  +
. groupBy cmpFst . sort
  +
cmpFst x y = fst x == fst y
  +
  +
-- All subsets (of an ordered set) whose sum of inverse squares is x
  +
findInvSq x y = f x $ zip3 y (map invSq y) (map sumInvSq $ init $ tails y)
  +
where
  +
f 0 _ = [[]]
  +
f x ((n, r, s):ns)
  +
| r > x = f x ns
  +
| s < x = []
  +
| otherwise = map (n :) (f (x - r) ns) ++ f x ns
  +
f _ _ = []
  +
  +
-- All numbers up to 85 that are divisible only by the primes
  +
-- 2 and 3 and are not divisible by 32 or 27.
  +
all23 = [n | a <- [0..4], b <- [0..2], let n = 2^a * 3^b, n <= 85]
  +
 
problem_152 = if verify
  +
then sum [n * length (findInvSq (1%2 - x) all23) |
  +
(x, n) <- only23]
  +
else undefined
 
</haskell>
 
</haskell>
   

Revision as of 13:52, 20 September 2007

Problem 151

Paper sheets of standard sizes: an expected-value problem.

Solution:

problem_151 = undefined

Problem 152

Writing 1/2 as a sum of inverse squares

Note that if p is an odd prime, the sum of inverse squares of all terms divisible by p must have reduced denominator not divisible by p.

Solution:

import Data.Ratio
import Data.List

invSq n = 1 % (n * n)
sumInvSq = sum . map invSq

subsets (x:xs) = let s = subsets xs in s ++ map (x :) s
subsets _      = [[]]

primes = 2 : 3 : 7 : [p | p <- [11, 13..83],
                          all (\q -> p `mod` q /= 0) [3, 5, 7]]

-- All subsets whose sum of inverse squares,
-- when added to x, does not contain a factor of p
pfree s x p = [(y, t) | t <- subsets s, let y =  x + sumInvSq t,
                        denominator y `mod` p /= 0]

-- Verify that we need not consider terms divisible by 11, or by any
-- prime greater than 13. Nor need we consider any term divisible
-- by 25, 27, 32, or 49.
verify = all (\p -> null $ tail $ pfree [p, 2*p..85] 0 p) $
         11 : dropWhile (< 17) primes ++ [25, 27, 32, 49]

-- All pairs (x, n) where x is a rational number whose reduced
-- denominator is not divisible by any prime greater than 3;
-- and n>0 is the number of sets of numbers up to 85 divisible
-- by a prime greater than 3, whose sum of inverse squares is x.
only23 = foldl f [(0, 1)] [13, 7, 5]
  where
    f x p = collect $ concatMap (g p) x
    g p (x, n) = map (\(a, b) -> (a, n * length b)) $ pfree (terms p) x p
    terms p = [n * p | n <- [1..85`div`p],
                       all (\q -> n `mod` q /= 0) [5, 7, 11, 13, 17]]
    collect = map (\z -> (fst $ head z, sum $ map snd z))
              . groupBy cmpFst . sort
    cmpFst x y = fst x == fst y

-- All subsets (of an ordered set) whose sum of inverse squares is x
findInvSq x y = f x $ zip3 y (map invSq y) (map sumInvSq $ init $ tails y)
  where
    f 0 _        = [[]]
    f x ((n, r, s):ns)
     | r > x     = f x ns
     | s < x     = []
     | otherwise = map (n :) (f (x - r) ns) ++ f x ns
    f _ _        = []

-- All numbers up to 85 that are divisible only by the primes
-- 2 and 3 and are not divisible by 32 or 27.
all23 = [n | a <- [0..4], b <- [0..2], let n = 2^a * 3^b, n <= 85]

problem_152 = if verify
                then sum [n * length (findInvSq (1%2 - x) all23) |
                            (x, n) <- only23]
                else undefined

Problem 153

Investigating Gaussian Integers

Solution:

problem_153 = undefined

Problem 154

Exploring Pascal's pyramid.

Solution:

problem_154 = undefined

Problem 155

Counting Capacitor Circuits.

Solution:

problem_155 = undefined

Problem 156

Counting Digits

Solution:

problem_156 = undefined

Problem 157

Solving the diophantine equation 1/a+1/b= p/10n

Solution:

problem_157 = undefined

Problem 158

Exploring strings for which only one character comes lexicographically after its neighbour to the left.

Solution:

problem_158 = undefined

Problem 159

Digital root sums of factorisations.

Solution:

problem_159 = undefined

Problem 160

Factorial trailing digits

Solution:

problem_160 = undefined