Even wilder performance increases
parent
bc28995115
commit
d4cf6b25c8
|
@ -16,24 +16,24 @@ NOTE: Once the chain starts the terms are allowed to go above one million.
|
|||
-}
|
||||
module Main where
|
||||
|
||||
import Data.List (genericLength, sortOn)
|
||||
import Data.List (sortOn)
|
||||
import Data.Ord (Down (Down))
|
||||
|
||||
main :: IO ()
|
||||
main = print ans
|
||||
|
||||
ans :: Integer
|
||||
ans :: Int
|
||||
ans = fst $ head $ sortOn (Down . snd) $ map collatzChainStartingAt [1..limit]
|
||||
|
||||
nextCollatz :: Integer -> Integer
|
||||
nextCollatz :: Int -> Int
|
||||
nextCollatz n
|
||||
| n == 1 = 0
|
||||
| even n = n `div` 2
|
||||
| odd n = 3*n + 1
|
||||
|
||||
collatzChainStartingAt :: Integer -> (Integer, Integer)
|
||||
collatzChainStartingAt :: Int -> (Int, Int)
|
||||
collatzChainStartingAt n = (n, s')
|
||||
where s' = genericLength $ takeWhile (/= 0) $ iterate nextCollatz n
|
||||
where s' = length $ takeWhile (/= 0) $ iterate nextCollatz n
|
||||
|
||||
limit :: Integer
|
||||
limit :: Int
|
||||
limit = 1_000_000
|
||||
|
|
Loading…
Reference in New Issue