About to try optimising my version
[advent-of-code-17.git] / src / advent15 / advent15other.hs
1 {-# LANGUAGE BangPatterns #-}
2 {-# OPTIONS_HADDOCK ignore-exports #-}
3 -- module Day15 (day15a, day15b) where
4
5 import Control.Arrow ((***))
6 import Data.Bits ((.&.))
7 import Data.Function (on)
8 import Data.List (stripPrefix)
9 import Data.Word (Word64)
10
11 -- | Returns the initial values for generators A and B.
12 -- parse :: String -> (Word64, Word64)
13 parse _ = (873, 583)
14 -- parse input = (read a, read b) where
15 -- [line1, line2] = lines input
16 -- Just a = stripPrefix "Generator A starts with " line1
17 -- Just b = stripPrefix "Generator B starts with " line2
18
19
20 main :: IO ()
21 main = do
22 print $ day15a "none"
23 print $ day15b "none"
24
25
26
27 genA, genB :: Int -> Int
28 genA x = x * 16807 `mod` 2147483647
29 genB x = x * 48271 `mod` 2147483647
30
31 day15a :: String -> Int
32 day15a input = length . filter id . take 40000000 $ zipWith (==) a b where
33 (a0, b0) = parse input
34 a = map (.&. 0xffff) $ iterate genA a0
35 b = map (.&. 0xffff) $ iterate genB b0
36
37 day15b :: String -> Int
38 day15b input = length . filter id . take 5000000 $ zipWith (==) a b where
39 (a0, b0) = parse input
40 a = map (.&. 0xffff) . filter ((== 0) . (`mod` 4)) $ iterate genA a0
41 b = map (.&. 0xffff) . filter ((== 0) . (`mod` 8)) $ iterate genB b0
42
43
44 -- -- | One step of generator A.
45 -- genA :: Word64 -> Word64
46 -- genA x = x * 16807 `mod` 2147483647
47
48 -- -- | One step of generator B.
49 -- genB :: Word64 -> Word64
50 -- genB x = x * 48271 `mod` 2147483647
51
52 -- -- | Step generator A until a multiple of 4.
53 -- genA' :: Word64 -> Word64
54 -- genA' x = let y = genA x in if y .&. 3 == 0 then y else genA' y
55
56 -- -- | Step generator A until a multiple of 8.
57 -- genB' :: Word64 -> Word64
58 -- genB' x = let y = genB x in if y .&. 7 == 0 then y else genB' y
59
60 -- -- | One step of both generators A and B.
61 -- gen :: (Word64, Word64) -> (Word64, Word64)
62 -- gen = genA *** genB
63
64 -- -- | Step both generators A and B until a multiple of 4 and 8 respectively.
65 -- gen' :: (Word64, Word64) -> (Word64, Word64)
66 -- gen' = genA' *** genB'
67
68 -- -- | prop> count p f x n == length (filter p . take n . tail $ iterate f x)
69 -- count :: (a -> Bool) -> (a -> a) -> a -> Int -> Int
70 -- count p f = count' 0 where
71 -- count' !k x 0 = k
72 -- count' !k x n = count' (if p y then k + 1 else k) y (n - 1) where y = f x
73
74 -- day15a :: String -> Int
75 -- day15a input =
76 -- count (uncurry ((==) `on` (.&. 0xffff))) gen (parse input) 40000000
77
78 -- day15b :: String -> Int
79 -- day15b input =
80 -- count (uncurry ((==) `on` (.&. 0xffff))) gen' (parse input) 5000000