Skip to content

Commit

Permalink
Complete 12 and 16.
Browse files Browse the repository at this point in the history
  • Loading branch information
FranklinChen committed Nov 18, 2012
1 parent 339f72b commit 0b30bb7
Show file tree
Hide file tree
Showing 7 changed files with 333 additions and 1 deletion.
38 changes: 38 additions & 0 deletions Answer/answer12.hs
@@ -0,0 +1,38 @@
{-|
Problem 12 of Project Euler
<http://projecteuler.net/problem=12>
The sequence of triangle numbers is generated by adding the natural numbers. So the 7th triangle number would be 1 + 2 + 3 + 4 + 5 + 6 + 7 = 28. The first ten terms would be:
1, 3, 6, 10, 15, 21, 28, 36, 45, 55, ...
Let us list the factors of the first seven triangle numbers:
1: 1
3: 1,3
6: 1,2,3,6
10: 1,2,5,10
15: 1,3,5,15
21: 1,3,7,21
28: 1,2,4,7,14,28
We can see that 28 is the first triangle number to have over five divisors.
What is the value of the first triangle number to have over five hundred divisors?
-}

module Main where

import Euler.Problem12 (firstTriangleNumberOverNDivisors)

main :: IO ()
main = putStrLn $ show answer


{-|
The answer.
TODO
-}
answer :: Integer
answer = firstTriangleNumberOverNDivisors 500
23 changes: 23 additions & 0 deletions Answer/answer16.hs
@@ -0,0 +1,23 @@
{-|
Problem 16 of Project Euler
<http://projecteuler.net/problem=16>
2^15 = 32768 and the sum of its digits is 3 + 2 + 7 + 6 + 8 = 26.
What is the sum of the digits of the number 2^1000?
-}

module Main where

import Euler.Problem16 (sumDigitsPowerOfTwo)

main :: IO ()
main = putStrLn $ show answer


{-|
The answer.
-}
answer :: Integer
answer = sumDigitsPowerOfTwo 1000
127 changes: 127 additions & 0 deletions Euler/Problem12.hs
@@ -0,0 +1,127 @@
{-|
Problem 12 of Project Euler
<http://projecteuler.net/problem=12>
The sequence of triangle numbers is generated by adding the natural numbers. So the 7th triangle number would be 1 + 2 + 3 + 4 + 5 + 6 + 7 = 28. The first ten terms would be:
1, 3, 6, 10, 15, 21, 28, 36, 45, 55, ...
Let us list the factors of the first seven triangle numbers:
1: 1
3: 1,3
6: 1,2,3,6
10: 1,2,5,10
15: 1,3,5,15
21: 1,3,7,21
28: 1,2,4,7,14,28
We can see that 28 is the first triangle number to have over five divisors.
What is the value of the first triangle number to have over five hundred divisors?
-}

module Euler.Problem12 where

{-
Assume there is an answer, so that head does not fail.
-}
firstTriangleNumberOverNDivisors :: Int -> Integer
firstTriangleNumberOverNDivisors = head . triangleNumbersOverNDivisors

{-
TODO: Could optimize by not computing all the factors.
-}
triangleNumbersOverNDivisors :: Int -> [Integer]
triangleNumbersOverNDivisors n =
[t | t <- triangleNumbers, numDivisors t > n]

{-|
Infinite stream of all the triangle numbers.
-}
triangleNumbers :: [Integer]
triangleNumbers = scanl1 (+) [1..]

{-
The number of divisors of @n@ does not actually require computation of
the divisors. It only requires computation of the prime factors.
For example, the factorization of 28 is 2, 2, 7.
To clarify:
2 has a count of 2 and 7 has a count of 1. Any divisor is a product
of powers of the prime factors, from 0 to the count of each factor.
Therefore, there are (2+1) * (1+1) == 6 divisors:
2^0 * 7^0 == 1
2^1 * 7^0 == 2
2^2 * 7^0 == 4
2^0 * 7^1 == 7
2^1 * 7^1 = 14
2^2 * 7^1 = 28
TODO: this can still be improved, because our problem does not
require computation of the number of divisors. It only requires
checking whether the number is about to exceed a specified bound.
-}
numDivisors :: Integer -> Int
numDivisors 1 = 1
numDivisors n = product [m+1 | m <- factorCounts n]

{-
For each prime factor, return the number of times it occurs in @n@,
which is assumed to be > 1.
-}
factorCounts :: Integer -> [Int]
factorCounts = countDuplicates . factorStream

{-
Utility function to group duplicates by their count.
Optimizes what can be done with standard Prelude functions:
countDuplicates xs == [length ys | ys <- List.group xs]
-}
countDuplicates :: Eq a => [a] -> [Int]
countDuplicates [] = []
countDuplicates (x:xs) = countDuplicatesOf x 1 xs

{-
Return possibly infinite stream of counts.
-}
countDuplicatesOf :: Eq a => a -> Int -> [a] -> [Int]
countDuplicatesOf _ count [] = [count]
countDuplicatesOf x count xs@(y:ys)
| x == y = countDuplicatesOf x (count+1) ys
| otherwise = count : countDuplicatesOf y 1 ys

{-
Factor @n@ using a given initial stream of factors to test.
-}
factorStream :: Integer -> [Integer]
factorStream = factorStreamFromStream possibleFactors

{-
Return finite stream of one factor at a time of @n@ starting from
a seed stream of possible factors. There may be duplicates, e.g.,
28 is factored as [2, 2, 7].
Non-primes in the candidate factor stream are skipped because
we divide out factors as we see them.
-}
factorStreamFromStream :: [Integer] -> Integer -> [Integer]
factorStreamFromStream factors@(factor:moreFactors) n
| factor*factor > n = [n]
| otherwise =
case n `quotRem` factor of
(q, 0) -> factor : factorStreamFromStream factors q
_ -> factorStreamFromStream moreFactors n


{-
A stream of possible factors to consider.
TODO: use a precomputed stream of primes?
-}
possibleFactors :: [Integer]
possibleFactors = 2 : [3, 5..]
23 changes: 23 additions & 0 deletions Euler/Problem16.hs
@@ -0,0 +1,23 @@
{-|
Problem 16 of Project Euler
<http://projecteuler.net/problem=16>
2^15 = 32768 and the sum of its digits is 3 + 2 + 7 + 6 + 8 = 26.
What is the sum of the digits of the number 2^1000?
-}

module Euler.Problem16 where

import qualified Data.Char as Char

{-|
Convert @2^n@ to base 10, then sum the digits.
Use infinite-precision arithmetic.
-}
sumDigitsPowerOfTwo :: Integer -> Integer
sumDigitsPowerOfTwo = sum . toBase10Digits . (2^)

toBase10Digits :: Integer -> [Integer]
toBase10Digits = map (toInteger . Char.digitToInt) . show
63 changes: 63 additions & 0 deletions Test/Test12.hs
@@ -0,0 +1,63 @@
{-# LANGUAGE TemplateHaskell #-}

module Main where

import Test.Framework.TH (defaultMainGenerator)

import Test.HUnit
import Test.Framework.Providers.HUnit (testCase)

import Test.QuickCheck
import Test.Framework.Providers.QuickCheck2 (testProperty)

import qualified Data.List as List

import Euler.Problem12 (firstTriangleNumberOverNDivisors,
triangleNumbers,
numDivisors,
countDuplicates)

main = $(defaultMainGenerator)

case_over_5_divisors =
firstTriangleNumberOverNDivisors 5 @?= 28

case_seventh_triangle_number =
triangleNumbers !! (7 - 1) @?= 28

{-
Make sure the triangle numbers are as they are defined.
-}
prop_triangle_numbers =
forAll (choose (1, 1000)) $
\n -> triangleNumbers !! (fromInteger n - 1) == sum [1..n]

--- numDivisors

-- 1: 1
case_numDivisors_1 =
numDivisors 1 @?= 1

-- 3: 1,3
case_numDivisors_3 =
numDivisors 3 @?= 2

-- 6: 1,2,3,6
case_numDivisors_6 =
numDivisors 6 @?= 4

-- 10: 1,2,5,10
case_numDivisors_10 =
numDivisors 10 @?= 4

-- 28: 1,2,4,7,14,28
case_numDivisors_28 =
numDivisors 28 @?= 6

{-
Check our optimized implementation.
-}
prop_countDuplicates =
forAll (listOf $ choose (1 :: Int, 3)) $
\xs ->
countDuplicates xs == [length ys | ys <- List.group xs]
18 changes: 18 additions & 0 deletions Test/Test16.hs
@@ -0,0 +1,18 @@
{-# LANGUAGE TemplateHaskell #-}

module Main where

import Test.Framework.TH (defaultMainGenerator)

import Test.HUnit
import Test.Framework.Providers.HUnit (testCase)

import Test.QuickCheck
import Test.Framework.Providers.QuickCheck2 (testProperty)

import Euler.Problem16 (sumDigitsPowerOfTwo)

main = $(defaultMainGenerator)

case_small =
sumDigitsPowerOfTwo 15 @?= 26
42 changes: 41 additions & 1 deletion project-euler-haskell.cabal
Expand Up @@ -22,7 +22,9 @@ source-repository head
library
build-depends: base
exposed-modules: Euler.Problem1,
Euler.Problem9
Euler.Problem9,
Euler.Problem12,
Euler.Problem16

executable answer1
hs-source-dirs: Answer
Expand All @@ -36,6 +38,18 @@ executable answer9
build-depends: base,
project-euler-haskell

executable answer12
hs-source-dirs: Answer
main-is: answer12.hs
build-depends: base,
project-euler-haskell

executable answer16
hs-source-dirs: Answer
main-is: answer16.hs
build-depends: base,
project-euler-haskell

-- detailed-0.9 problem integrating with HUnit?
test-suite test-problem1
type: exitcode-stdio-1.0
Expand All @@ -62,3 +76,29 @@ test-suite test-problem9
test-framework-hunit,
test-framework-quickcheck2,
test-framework-th

test-suite test-problem12
type: exitcode-stdio-1.0
hs-source-dirs: Test
main-is: Test12.hs
build-depends: base,
project-euler-haskell,
HUnit,
QuickCheck,
test-framework,
test-framework-hunit,
test-framework-quickcheck2,
test-framework-th

test-suite test-problem16
type: exitcode-stdio-1.0
hs-source-dirs: Test
main-is: Test16.hs
build-depends: base,
project-euler-haskell,
HUnit,
QuickCheck,
test-framework,
test-framework-hunit,
test-framework-quickcheck2,
test-framework-th

0 comments on commit 0b30bb7

Please sign in to comment.