never executed always true always false
1 {-|
2 Module: Y2015.D18
3 Description: Advent of Code Day 18 Solutions.
4 License: MIT
5 Maintainer: @tylerjl
6
7 Solutions to the day 18 set of problems for <adventofcode.com>.
8 -}
9
10 {-# LANGUAGE QuasiQuotes #-}
11
12 module Y2015.D18 (animateLights, animateStuckLights) where
13
14 import Data.Array.Repa ((:.)(..), Array, DIM2, U, Z(..))
15 import qualified Data.Array.Repa as R
16 import Data.Array.Repa.Stencil (Boundary(..), Stencil)
17 import Data.Array.Repa.Stencil.Dim2 (makeStencil2, mapStencil2, stencil2)
18 import Data.Bits ((.|.), Bits(..))
19 import Data.Vector.Unboxed.Base (Unbox)
20
21 type Lights a = Array U DIM2 a
22
23 -- |Animates an example light grid
24 animateLights :: String -- ^ Raw string representing starting state
25 -> Int -- ^ Number of cycles to let animations repeat
26 -> Int -- ^ Number of lit lights
27 animateLights s n = R.sumAllS $ iterate animate (initialGrid s) !! n
28
29 -- |Animates an example light grid with stuck lights
30 animateStuckLights :: String -- ^ Raw string representing starting state
31 -> Int -- ^ Number of cycles to let animations repeat
32 -> Int -- ^ Number of lit lights
33 animateStuckLights s n = R.sumAllS $ iterate (stuck e . animate) g' !! n
34 where g = initialGrid s
35 e = R.extent g
36 g' = stuck e g
37
38 stuck :: (Bits a, Num a, Unbox a) => R.DIM2 -> Lights a -> Lights a
39 stuck e = R.computeS . R.zipWith (.|.) (stuckLights e)
40
41 stuckLights :: (Num a, Unbox a) => R.DIM2 -> Lights a
42 stuckLights sh = R.fromListUnboxed sh [corner x | x <- [1..s]]
43 where s = R.size sh
44 i = truncate ((sqrt $ fromIntegral s) :: Double)
45 corner 1 = 1
46 corner n | n == i = 1
47 | n == s = 1
48 | n == (s - i) + 1 = 1
49 | otherwise = 0
50
51 animate :: Lights Int -> Lights Int
52 animate grid = R.computeS $ R.zipWith step grid adjacent
53 where adjacent = mapStencil2 (BoundConst 0) stencil grid
54
55 step :: Int -> Int -> Int
56 step 1 2 = 1
57 step 1 3 = 1
58 step 0 3 = 1
59 step _ _ = 0
60
61 stencil :: Stencil DIM2 Int
62 stencil = [stencil2| 1 1 1
63 1 0 1
64 1 1 1 |]
65
66 initialGrid :: (Num a, Unbox a) => String -> Lights a
67 initialGrid s = R.fromListUnboxed (Z :. size :. size :: R.DIM2) lights
68 where scrubbed = filter (/= '\n') s
69 size = truncate ((sqrt $ fromIntegral $ length scrubbed) :: Double)
70 lights = map toLight scrubbed
71 toLight '#' = 1
72 toLight _ = 0