Add solutions for problems 28-32.
This commit is contained in:
parent
cfd8dbdf1d
commit
769787ab48
16
Euler.hs
16
Euler.hs
|
|
@ -12,17 +12,19 @@ module Euler
|
||||||
, primes
|
, primes
|
||||||
, zipArraysWith
|
, zipArraysWith
|
||||||
, RangeIx(..)
|
, RangeIx(..)
|
||||||
, digitsOf
|
|
||||||
, divisors
|
, divisors
|
||||||
, properDivisors
|
, properDivisors
|
||||||
, toDecimal
|
, toDecimal
|
||||||
, fromDecimal
|
, fromDecimal
|
||||||
|
, toDigits
|
||||||
|
, fromDigits
|
||||||
, module Control.Applicative
|
, module Control.Applicative
|
||||||
, module Control.Arrow
|
, module Control.Arrow
|
||||||
, module Control.Monad
|
, module Control.Monad
|
||||||
, module Data.Function
|
, module Data.Function
|
||||||
, module Data.List
|
, module Data.List
|
||||||
, module Data.Ratio
|
, module Data.Ratio
|
||||||
|
, module Data.Tuple
|
||||||
, module Data.Word
|
, module Data.Word
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
|
@ -36,6 +38,7 @@ import Data.Array.Unboxed
|
||||||
import Data.Function
|
import Data.Function
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Ratio
|
import Data.Ratio
|
||||||
|
import Data.Tuple
|
||||||
import Data.Word
|
import Data.Word
|
||||||
|
|
||||||
import qualified Control.Monad.ST.Lazy as LST
|
import qualified Control.Monad.ST.Lazy as LST
|
||||||
|
|
@ -77,9 +80,6 @@ zipArraysWith :: (IArray arrA a, IArray arrB b, IArray arrC c, RangeIx i)
|
||||||
zipArraysWith f as bs = array newRange $ [ (i, f (as!i) (bs!i)) | i <- range newRange ]
|
zipArraysWith f as bs = array newRange $ [ (i, f (as!i) (bs!i)) | i <- range newRange ]
|
||||||
where newRange = intersectBounds (bounds as) (bounds bs)
|
where newRange = intersectBounds (bounds as) (bounds bs)
|
||||||
|
|
||||||
digitsOf :: (Read a, Show a, Integral a) => a -> [a]
|
|
||||||
digitsOf = map (read . (:[])) . show
|
|
||||||
|
|
||||||
divisors :: Integral a => a -> [a]
|
divisors :: Integral a => a -> [a]
|
||||||
divisors n = nub $ concat [ [m, q] | m <- takeWhile (\x -> x^2 <= n) [1..], let (q, r) = n `divMod` m, r == 0 ]
|
divisors n = nub $ concat [ [m, q] | m <- takeWhile (\x -> x^2 <= n) [1..], let (q, r) = n `divMod` m, r == 0 ]
|
||||||
|
|
||||||
|
|
@ -105,7 +105,6 @@ toDecimal' n m = first (map fst) $ second (map fst) $ collect [] xs
|
||||||
fromDecimal :: Decimal -> Rational
|
fromDecimal :: Decimal -> Rational
|
||||||
fromDecimal (Decimal n ps rs) = (n % 1) + (p + r) * (1 % 10 ^ length ps)
|
fromDecimal (Decimal n ps rs) = (n % 1) + (p + r) * (1 % 10 ^ length ps)
|
||||||
where (p, r) = (fromDigits ps % 1, fromDigits rs % (10 ^ length rs - 1))
|
where (p, r) = (fromDigits ps % 1, fromDigits rs % (10 ^ length rs - 1))
|
||||||
fromDigits = foldl' (\s d -> 10 * s + fromIntegral d) 0
|
|
||||||
|
|
||||||
deriving instance Eq Decimal
|
deriving instance Eq Decimal
|
||||||
deriving instance Ord Decimal
|
deriving instance Ord Decimal
|
||||||
|
|
@ -116,3 +115,10 @@ instance Show Decimal where
|
||||||
| null rs = show n ++ "." ++ concat (map show ps)
|
| null rs = show n ++ "." ++ concat (map show ps)
|
||||||
| otherwise = show n ++ "." ++ concat (map show ps)
|
| otherwise = show n ++ "." ++ concat (map show ps)
|
||||||
++ "(" ++ concat (map show rs) ++ ")"
|
++ "(" ++ concat (map show rs) ++ ")"
|
||||||
|
|
||||||
|
toDigits :: (Integral a, Integral b) => a -> [b]
|
||||||
|
toDigits = reverse . unfoldr (\x ->
|
||||||
|
if x == 0 then Nothing else Just (first fromIntegral $ swap (x `divMod` 10)))
|
||||||
|
|
||||||
|
fromDigits :: (Integral a, Integral b) => [a] -> b
|
||||||
|
fromDigits = foldl' (\a b -> 10 * a + fromIntegral b) 0
|
||||||
|
|
|
||||||
|
|
@ -1,2 +1,2 @@
|
||||||
import Euler
|
import Euler
|
||||||
main = print $ sum $ digitsOf $ product [1..100]
|
main = print $ sum $ toDigits $ product [1..100]
|
||||||
|
|
|
||||||
|
|
@ -0,0 +1,23 @@
|
||||||
|
-- Starting with the number 1 and moving to the right in a clockwise direction
|
||||||
|
-- a 5 by 5 spiral is formed as follows:
|
||||||
|
--
|
||||||
|
-- 21 22 23 24 25
|
||||||
|
-- 20 7 8 9 10
|
||||||
|
-- 19 6 1 2 11
|
||||||
|
-- 18 5 4 3 12
|
||||||
|
-- 17 16 15 14 13
|
||||||
|
--
|
||||||
|
-- It can be verified that the sum of the numbers on the diagonals is 101.
|
||||||
|
--
|
||||||
|
-- What is the sum of the numbers on the diagonals in a 1001 by 1001 spiral
|
||||||
|
-- formed in the same way?
|
||||||
|
|
||||||
|
ne = 1 : zipWith (+) nw [2,4..]
|
||||||
|
se = zipWith (+) ne [2,4..]
|
||||||
|
sw = zipWith (+) se [2,4..]
|
||||||
|
nw = zipWith (+) sw [2,4..]
|
||||||
|
|
||||||
|
-- Sum of diagonals of an m by m spiral; m = 2*n + 1.
|
||||||
|
diagSum n = sum (take (n+1) ne ++ take n se ++ take n sw ++ take n nw)
|
||||||
|
|
||||||
|
main = print $ (diagSum 2, diagSum 500)
|
||||||
|
|
@ -0,0 +1,4 @@
|
||||||
|
-- How many distinct terms are in the sequence generated by a^b
|
||||||
|
-- for 2 ≤ a ≤ 100 and 2 ≤ b ≤ 100?
|
||||||
|
import Euler
|
||||||
|
main = print $ length $ nub [ a^b | a <- [2..100], b <- [2..100] ]
|
||||||
|
|
@ -0,0 +1,4 @@
|
||||||
|
-- Find the sum of all the numbers that can be written as the sum of fifth
|
||||||
|
-- powers of their digits.
|
||||||
|
import Euler
|
||||||
|
main = print $ sum $ filter (\n -> sum (map (^5) (toDigits n)) == n) [2..(6 * 9^5)]
|
||||||
|
|
@ -0,0 +1,19 @@
|
||||||
|
-- In England the currency is made up of pound, £, and pence, p, and there are eight coins in general circulation:
|
||||||
|
--
|
||||||
|
-- 1p, 2p, 5p, 10p, 20p, 50p, £1 (100p) and £2 (200p)
|
||||||
|
--
|
||||||
|
-- How many different ways can £2 be made using any number of coins?
|
||||||
|
|
||||||
|
import Data.Array
|
||||||
|
import Euler
|
||||||
|
|
||||||
|
coins = listArray (0,7) [1,2,5,10,20,50,100,200] :: Array Int Int
|
||||||
|
|
||||||
|
nWays total = arr ! (total, snd (bounds coins))
|
||||||
|
where
|
||||||
|
arr = array ((0, fst (bounds coins)), (total, snd (bounds coins)))
|
||||||
|
[ ((n, c), sum [ arr ! (n - (coins!c'), c') + if n == coins!c' then 1 else 0
|
||||||
|
| c' <- [fst (bounds coins)..c], coins!c' <= n ])
|
||||||
|
| n <- [0..total], c <- indices coins ]
|
||||||
|
|
||||||
|
main = print $ nWays 200
|
||||||
|
|
@ -0,0 +1,35 @@
|
||||||
|
-- We shall say that an n-digit number is pandigital if it makes use of all the
|
||||||
|
-- digits 1 to n exactly once; for example, the 5-digit number, 15234, is 1
|
||||||
|
-- through 5 pandigital.
|
||||||
|
--
|
||||||
|
-- The product 7254 is unusual, as the identity, 39 × 186 = 7254, containing
|
||||||
|
-- multiplicand, multiplier, and product is 1 through 9 pandigital.
|
||||||
|
--
|
||||||
|
-- Find the sum of all products whose multiplicand/multiplier/product identity
|
||||||
|
-- can be written as a 1 through 9 pandigital.
|
||||||
|
--
|
||||||
|
-- HINT: Some products can be obtained in more than one way so be sure to only
|
||||||
|
-- include it once in your sum.
|
||||||
|
|
||||||
|
import Euler
|
||||||
|
|
||||||
|
partitions [] = [([],[])]
|
||||||
|
partitions (x:xs) = map (first (x:)) ps ++ map (second (x:)) ps
|
||||||
|
where ps = partitions xs
|
||||||
|
|
||||||
|
main = print $ sum $ nub $ do
|
||||||
|
(as, as') <- partitions [1..9]
|
||||||
|
guard $ not $ null as
|
||||||
|
(bs, cs) <- partitions as'
|
||||||
|
guard $ not $ null bs
|
||||||
|
guard $ not $ null cs
|
||||||
|
guard $ length as <= length bs
|
||||||
|
guard $ length as <= length cs
|
||||||
|
guard $ length bs <= length cs
|
||||||
|
guard $ length as + length bs >= length cs
|
||||||
|
x <- fromDigits <$> permutations as
|
||||||
|
y <- fromDigits <$> permutations bs
|
||||||
|
guard $ x < y
|
||||||
|
let p = x * y
|
||||||
|
guard $ sort (toDigits p) == cs
|
||||||
|
return p
|
||||||
Loading…
Reference in New Issue