Day 15 - removed old solution in favour of faster strict solution

This commit is contained in:
Jonathan Chan 2017-12-16 11:14:01 -08:00
parent 871855ff85
commit 5969de9996
2 changed files with 19 additions and 40 deletions

36
15.hs
View File

@ -1,21 +1,23 @@
import Data.Int (Int16) {-# LANGUAGE BangPatterns #-}
import Data.Function (on)
import Data.Bits ((.&.))
gen :: Int -> Int -> Int -> [Int] divisor = 2147483647
gen divisor factor seed = iterate (next divisor factor) seed factors = (16807, 48271)
where next d f i = (f * i) `mod` d seed = (634, 301)
judge :: Int -> [Int] -> [Int] -> Int count :: (Int, Int) -> (Int, Int) -> Int -> Int -> Int
judge n a b = length . filter (uncurry eq) . take n $ zip a b count pair masks acc times =
where eq i j = (fromIntegral i :: Int16) == (fromIntegral j :: Int16) if times == 0 then acc else
let !next = nextMaskBy <$$> factors <**> masks <**> pair
divisible :: Int -> Int -> Bool !eq = fromEnum $ uncurry ((==) `on` (.&. 0xffff)) next
divisible d = (== 0) . (`mod` d) in count next masks (acc + eq) (times - 1)
where
h <$$> (x, y) = (h x, h y)
(f, g) <**> (x, y) = (f x, g y)
nextMaskBy f m s = let t = (f * s) `mod` divisor in if (t .&. m) == 0 then t else nextMaskBy f m t
main :: IO () main :: IO ()
main = do main = do
let genA = gen 2147483647 16807 634 print $ count seed (0, 0) 0 40000000
genB = gen 2147483647 48271 301 print $ count seed (3, 7) 0 5000000
gen4A = filter (divisible 4) genA
gen8B = filter (divisible 8) genB
print $ judge 40000000 genA genB
print $ judge 5000000 gen4A gen8B

View File

@ -1,23 +0,0 @@
{-# LANGUAGE BangPatterns #-}
import Data.Function (on)
import Data.Bits ((.&.))
divisor = 2147483647
factors = (16807, 48271)
seed = (634, 301)
count :: (Int, Int) -> (Int, Int) -> Int -> Int -> Int
count pair masks acc times =
if times == 0 then acc else
let !next = nextMaskBy <$$> factors <**> masks <**> pair
!eq = fromEnum $ uncurry ((==) `on` (.&. 0xffff)) next
in count next masks (acc + eq) (times - 1)
where
h <$$> (x, y) = (h x, h y)
(f, g) <**> (x, y) = (f x, g y)
nextMaskBy f m s = let t = (f * s) `mod` divisor in if (t .&. m) == 0 then t else nextMaskBy f m t
main :: IO ()
main = do
print $ count seed (0, 0) 0 40000000
print $ count seed (3, 7) 0 5000000