3

Going through Project Euler I am comparing my solutions to the ones here.

For question 8 my code produces the correct answer (confirmed via the check sum on the website) 23514624000.

module Main where

import Data.List

main = do
    print $ last (sort eulerEight)


eulerEight = doCalc [ x | x <- toDigits 7316717653133062491922511967442657474235534919493496983520312774506326239578318016984801869478851843858615607891129494954595017379583319528532088055111254069874715852386305071569329096329522744304355766896648950445244523161731856403098711121722383113622298934233803081353362766142828064444866452387493035890729629049156044077239071381051585930796086670172427121883998797908792274921901699720888093776657273330010533678812202354218097512545405947522435258490771167055601360483958644670632441572215539753697817977846174064955149290862569321978468622482839722413756570560574902614079729686524145351004748216637048440319989000889524345065854122758866688116427171479924442928230863465674813919123162824586178664583591245665294765456828489128831426076900422421902267105562632111110937054421750694165896040807198403850962455444362981230987879927244284909188845801561660979191338754992005240636899125607176060588611646710940507754100225698315520005593572972571636269561882670428252483600823257530420752963450]
    where
        doCalc (_:[]) = []
        doCalc (x:xs) = if 0 `notElem` take 13 (x:xs) && length (x:xs) > 12
                then product (take 13 (x:xs)) : doCalc xs
                else doCalc xs

toDigits n 
 | n < 1 = []
 | otherwise = toDigits (n `div` 10) ++ [n `mod` 10]

I realised this could be a lot better to so checked the solution here and it doesn't seem to be correct.

import Data.Char (digitToInt)
import Data.List

problem_8 = do
        str <- readFile "number.txt"
        -- This line just converts our str(ing) to a list of 1000 Ints
        let number = map digitToInt (concat $ lines str)
        print $ maximum $ map (product . take 13) (tails number)

I've changed the value of take 5 to take 13 as per the question on the Project Euler site, however the code above produces an incorrect answer of 2091059712. I've checked the number in number.txt is correct and that it has the full 1000 digits for both examples. Can anybody shed light on why the outputs are different? ( im thinking maybe to do with the fact it uses tails and not tail, but im not sure)

Martijn Pieters
  • 1,048,767
  • 296
  • 4,058
  • 3,343
Dave0504
  • 1,057
  • 11
  • 30

2 Answers2

6

What is happening is that digitToInt returns an Int, which on 32-bit systems is too short to hold the test numbers when 5 is increased to 13. Change it to (fromIntegral . digitToInt) and it works correctly.

Ørjan Johansen
  • 18,119
  • 3
  • 43
  • 53
2

The problem was already identified as an Int overflow, but the wiki code itself is incorrect. It doesn't truncate the list properly, and might produce incorrect result, depending on input data (i.e. it produces the correct result here by a lucky chance).

Imagine a string of digits which ends in a 0 followed by 12 9s. The code will take 9^12 into consideration incorrectly, when calculating the maximum value. Even simpler, for a 1000 zeroes it will produce 1 as an answer.

We can achieve an automagical truncation, due to the properties of zipping:

import Data.Char
import Data.List

euler_8 = do
   str <- readFile "numbers.txt"
   print . maximum . map product
         . foldr (zipWith (:)) (repeat [])   -- here
         . take 13 . tails . map (fromIntegral . digitToInt)
         . concat . lines $ str

Your code though is correct, but has some issues:

  • [x | x <- xs] is just xs
  • last (sort xs) is just maximum xs, which is faster
  • appending on the right of a recursive call is a known source for inefficiency. it is better even to append on the left and reverse in the end, but the following transformation is more Haskellian:
toDigits n xs  -- to be called as `toDigits n []`
 | n < 1 = xs
 | otherwise = toDigits (n `div` 10) ((n `mod` 10) : xs)
Will Ness
  • 70,110
  • 9
  • 98
  • 181
  • could you please explain what you have done there with the zipping? The point free notation makes it hard for me to follow as a noob. – matt Jan 26 '16 at 16:23
  • 1
    @matthias point-free is actually easier for me to comprehend. :) just read the `.` as "of": *"print the result of `maximum` of `map product` of the result of folding `zipWith (:)` over the lists with `repeat [] = [[], [], [], [], .....]` as the right-most element"*. The key is the identity `foldr f z [a,b,...,n] == f a (f b (f ..... (f n z) .....))`. So with `take 3`, we'd get `zipWith (:) xs (zipWith (:) (tail xs) (zipWith (:) (drop 2 xs) (repeat [])))`. i.e. for `xs = [a,b,c,d]` this would produce `[a:b:c:[], b:c:d:[]]`. Zipping stops on the shortest list, so there's no `c:d:e:[]` ... – Will Ness Jan 26 '16 at 16:49
  • 1
    .... because there's no `e`! -- what we had was `zipWith (:) [a,b,c,d] (zipWith (:) [b,c,d] (zipWith (:) [c,d] (repeat [])))`. so the effect was, that the extra tails were automatically ignored, with no extra effort on our part. :) And all our produced sublists were of the same length -- 3. – Will Ness Jan 26 '16 at 16:51
  • thank you. I wrote `maximum $ map product $ foldr (zipWith (:)) (repeat[]) $ take 13 $ iterate tail x` I had problems with what with the empty lists and your post helped. It does make it easier I read it out the way you do but I still find it a bit difficult :) – matt Jan 26 '16 at 17:03
  • also, what did on the `toDigts` (acc style I guess?) is just brilliant. Haskell is amazing! – matt Jan 26 '16 at 17:08
  • @matthias no, not accumulation; *mapping*. --- this code is equivalent to `takeWhile ((==13).length) . map (take 13) . tails`, only more efficient. – Will Ness Jan 26 '16 at 17:10
  • 1
    I was referring tot he `toDigits` n xs . you are using xs as an accumulator no ? – matt Jan 26 '16 at 17:20