Difference between revisions of "Euler problems/71 to 80"

From HaskellWiki
Jump to navigation Jump to search
(Faster (5X) solution to problem 74)
Line 96: Line 96:
 
problem_74 = length $ filter (\(_,b) -> isChainLength 59 b) $ zip ([0..] :: [Integer]) $ take 1000000 $ elems factorDigits
 
problem_74 = length $ filter (\(_,b) -> isChainLength 59 b) $ zip ([0..] :: [Integer]) $ take 1000000 $ elems factorDigits
 
</haskell>
 
</haskell>
  +
  +
Slightly faster solution :
  +
<haskell>{-# OPTIONS_GHC -fbang-patterns #-}
  +
import Data.List
  +
import Data.Array
  +
  +
explode 0 = []
  +
explode n = n `mod` 10 : explode (n `quot` 10)
  +
  +
count :: (a -> Bool) -> [a] -> Int
  +
count pred xs = lgo 0 xs
  +
where lgo !c [] = c
  +
lgo !c (y:ys) | pred y = lgo (c + 1) ys
  +
| otherwise = lgo c ys
  +
  +
known = [([1,2,145,40585],1),([871,45361,872,45362],2),([169,363601,1454],3)]
  +
mChain = array (1,1000000) $ (concat $ expand known)
  +
++ [(x, n)|x<-[3..1000000]
  +
, not $ x `elem` concat (map fst known)
  +
, let n = 1 + chain (sumFactDigits x)]
  +
where expand [] = []
  +
expand ((xs,len):xxs) = map (flip (,) len) xs : expand xxs
  +
chain x | x <= 1000000 = mChain ! x
  +
| otherwise = 1 + chain (sumFactDigits x)
  +
  +
sumFactDigits = foldl' (\a b -> a + facts !! b) 0 . explode
  +
facts = scanl (*) 1 [1..9]
  +
  +
problem_74 = count (== 60) $ elems mChain</haskell>
   
 
== [http://projecteuler.net/index.php?section=view&id=75 Problem 75] ==
 
== [http://projecteuler.net/index.php?section=view&id=75 Problem 75] ==

Revision as of 16:04, 30 August 2007

Problem 71

Listing reduced proper fractions in ascending order of size.

Solution:

import Data.Ratio (Ratio, (%), numerator)

fractions :: [Ratio Integer]
fractions = [f | d <- [1..1000000], let n = (d * 3) `div` 7, let f = n%d, f /= 3%7]

problem_71 :: Integer
problem_71 = numerator $ maximum $ fractions

Problem 72

How many elements would be contained in the set of reduced proper fractions for d ≤ 1,000,000?

Solution:

Using the Farey Sequence method, the solution is the sum of phi (n) from 1 to 1000000.

See problem 69 for phi function

problem_72 = sum [phi x|x <- [1..1000000]]

Problem 73

How many fractions lie between 1/3 and 1/2 in a sorted set of reduced proper fractions?

Solution:

import Data.Ratio (Ratio, (%), numerator, denominator)

median :: Ratio Int -> Ratio Int -> Ratio Int
median a b = ((numerator a) + (numerator b)) % ((denominator a) + (denominator b))

count :: Ratio Int -> Ratio Int -> Int
count a b
    | d > 10000 = 1
    | otherwise   = count a m + count m b
    where
        m = median a b
        d = denominator m

problem_73 :: Int
problem_73 = (count (1%3) (1%2)) - 1

Problem 74

Determine the number of factorial chains that contain exactly sixty non-repeating terms.

Solution:

import Data.Array (Array, array, (!), elems)
import Data.Char (ord)
import Data.List (foldl1')
import Prelude hiding (cycle)

fact :: Integer -> Integer
fact 0 = 1
fact n = foldl1' (*) [1..n]

factorDigits :: Array Integer Integer
factorDigits = array (0,2177281) [(x,n)|x <- [0..2177281], let n = sum $ map (\y -> fact (toInteger $ ord y - 48)) $ show x]

cycle :: Integer -> Integer
cycle 145    = 1
cycle 169    = 3
cycle 363601 = 3
cycle 1454   = 3
cycle 871    = 2
cycle 45361  = 2
cycle 872    = 2
cycle 45362  = 2
cycle _      = 0

isChainLength :: Integer -> Integer -> Bool
isChainLength len n
    | len < 0   = False
    | t         = isChainLength (len-1) n'
    | otherwise = (len - c) == 0
    where
        c = cycle n
        t = c == 0
        n' = factorDigits ! n

-- | strict version of the maximum function
maximum' :: (Ord a) => [a] -> a
maximum' [] = undefined
maximum' [x] = x
maximum' (a:b:xs) = let m = max a b in m `seq` maximum' (m : xs)

problem_74 :: Int
problem_74 = length $ filter (\(_,b) -> isChainLength 59 b) $ zip ([0..] :: [Integer]) $ take 1000000 $ elems factorDigits

Slightly faster solution :

{-# OPTIONS_GHC -fbang-patterns #-}
import Data.List
import Data.Array

explode 0 = []
explode n = n `mod` 10 : explode (n `quot` 10)

count :: (a -> Bool) -> [a] -> Int
count pred xs = lgo 0 xs
    where lgo !c [] = c
          lgo !c (y:ys) | pred y = lgo (c + 1) ys
                        | otherwise = lgo c ys

known = [([1,2,145,40585],1),([871,45361,872,45362],2),([169,363601,1454],3)]
mChain = array (1,1000000) $ (concat $ expand known)
         ++ [(x, n)|x<-[3..1000000]
            , not $ x `elem` concat (map fst known)
            , let n = 1 + chain (sumFactDigits x)]
    where expand [] = []
          expand ((xs,len):xxs) = map (flip (,) len) xs : expand xxs
          chain x | x <= 1000000 = mChain ! x
                  | otherwise = 1 + chain (sumFactDigits x)

sumFactDigits = foldl' (\a b -> a + facts !! b) 0 . explode
facts = scanl (*) 1 [1..9]

problem_74 = count (== 60) $ elems mChain

Problem 75

Find the number of different lengths of wire can that can form a right angle triangle in only one way.

Solution: This is only slightly harder than problem 39. The search condition is simpler but the search space is larger.

problem_75 = length . filter ((== 1) . length) $ group perims
    where  perims = sort [scale*p | p <- pTriples, scale <- [1..10^6 `div` p]]
           pTriples = [p |
                       n <- [1..1000],
                       m <- [n+1..1000],
                       even n || even m,
                       gcd n m == 1,
                       let a = m^2 - n^2,
                       let b = 2*m*n,
                       let c = m^2 + n^2,
                       let p = a + b + c,
                       p <= 10^6]

Problem 76

How many different ways can one hundred be written as a sum of at least two positive integers?

Solution:

Calculated using Euler's pentagonal formula and a list for memoization.

partitions = 1 : [sum [s * partitions !! p| (s,p) <- zip signs $ parts n]| n <- [1..]]
    where
        signs = cycle [1,1,(-1),(-1)]
        suite = map penta $ concat [[n,(-n)]|n <- [1..]]
        penta n = n*(3*n - 1) `div` 2
        parts n = takeWhile (>= 0) [n-x| x <- suite]

problem_76 = partitions !! 100 - 1

Problem 77

What is the first value which can be written as the sum of primes in over five thousand different ways?

Solution:

Brute force but still finds the solution in less than one second.

combinations acc 0 _ = [acc]
combinations acc _ [] = []
combinations acc value prim@(x:xs) = combinations (acc ++ [x]) value' prim' ++ combinations acc value xs
    where
        value' = value - x
        prim' = dropWhile (>value') prim

problem_77 :: Integer
problem_77 = head $ filter f [1..]
    where
        f n = (length $ combinations [] n $ takeWhile (<n) primes) > 5000

Problem 78

Investigating the number of ways in which coins can be separated into piles.

Solution:

Same as problem 76 but using array instead of lists to speedup things.

import Data.Array

partitions :: Array Int Integer
partitions = array (0,1000000) $ (0,1) : [(n,sum [s * partitions ! p| (s,p) <- zip signs $ parts n])| n <- [1..1000000]]
    where
        signs = cycle [1,1,(-1),(-1)]
        suite = map penta $ concat [[n,(-n)]|n <- [1..]]
        penta n = n*(3*n - 1) `div` 2
        parts n = takeWhile (>= 0) [n-x| x <- suite]

problem_78 :: Int
problem_78 = head $ filter (\x -> (partitions ! x) `mod` 1000000 == 0) [1..]

Problem 79

By analysing a user's login attempts, can you determine the secret numeric passcode?

Solution:

A bit ugly but works fine

import Data.List

problem_79 :: String -> String
problem_79 file = map fst $ sortBy (\(_,a) (_,b) -> compare (length b) (length a)) $ zip digs order
    where
        nums = lines file
        digs = map head $ group $ sort $ filter (\c -> c >= '0' && c <= '9') file
        prec = concatMap (\(x:y:z:_) -> [[x,y],[y,z],[x,z]]) nums
        order = map (\n -> map head $ group $ sort $ map (\(_:x:_) -> x) $ filter (\(x:_) -> x == n) prec) digs

Problem 80

Calculating the digital sum of the decimal digits of irrational square roots.

Solution:

import Data.List ((\\))

hundreds :: Integer -> [Integer]
hundreds n = hundreds' [] n
    where
        hundreds' acc 0 = acc
        hundreds' acc n = hundreds' (m : acc) d
            where
                (d,m) = divMod n 100

squareDigs :: Integer -> [Integer]
squareDigs n = p : squareDigs' p r xs
    where
        (x:xs) = hundreds n ++ repeat 0
        p = floor $ sqrt $ fromInteger x
        r = x - (p^2)

squareDigs' :: Integer -> Integer -> [Integer] -> [Integer]
squareDigs' p r (x:xs) = x' : squareDigs' (p*10 + x') r' xs
    where
        n = 100*r + x
        (x',r') = last $ takeWhile (\(_,a) -> a >= 0) $ scanl (\(_,b) (a',b') -> (a',b-b')) (0,n) rs
        rs = [y|y <- zip [1..] [(20*p+1),(20*p+3)..]]
        
sumDigits n = sum $ take 100 $ squareDigs n

problem_80 :: Integer
problem_80 = sum $ map sumDigits [x|x <- [1..100] \\ [n^2|n<-[1..10]]]