1
0
Fork 0

Add performance improvement

main
Bill Ewanick 2023-09-27 16:51:16 -04:00
parent 7594cb1422
commit bc28995115
1 changed files with 5 additions and 4 deletions

View File

@ -16,14 +16,14 @@ NOTE: Once the chain starts the terms are allowed to go above one million.
-} -}
module Main where module Main where
import Data.List (sortOn) import Data.List (genericLength, sortOn)
import Data.Ord (Down (Down)) import Data.Ord (Down (Down))
main :: IO () main :: IO ()
main = print ans main = print ans
ans :: Integer ans :: Integer
ans = head $ head $ sortOn (Down . length) $ map collatzChainStartingAt [1..limit] ans = fst $ head $ sortOn (Down . snd) $ map collatzChainStartingAt [1..limit]
nextCollatz :: Integer -> Integer nextCollatz :: Integer -> Integer
nextCollatz n nextCollatz n
@ -31,8 +31,9 @@ nextCollatz n
| even n = n `div` 2 | even n = n `div` 2
| odd n = 3*n + 1 | odd n = 3*n + 1
collatzChainStartingAt :: Integer -> [Integer] collatzChainStartingAt :: Integer -> (Integer, Integer)
collatzChainStartingAt n = takeWhile (/= 0) $ iterate nextCollatz n collatzChainStartingAt n = (n, s')
where s' = genericLength $ takeWhile (/= 0) $ iterate nextCollatz n
limit :: Integer limit :: Integer
limit = 1_000_000 limit = 1_000_000