Skip to content

Commit a9ac8e2

Browse files
committed
Solve day 14 part 1 for demo
1 parent cc60038 commit a9ac8e2

File tree

1 file changed

+54
-6
lines changed

1 file changed

+54
-6
lines changed

day14/src/Day14.hs

Lines changed: 54 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,9 @@
1-
{-# LANGUAGE OverloadedRecordDot #-}
1+
{-# LANGUAGE DeriveFunctor, NoFieldSelectors, OverloadedRecordDot #-}
22

33
import System.Environment (getArgs)
44
import System.IO (readFile')
5+
import Data.List (sort)
6+
import Control.Monad (join)
57

68
-- | Splits on the given value.
79
split :: Eq a => a -> [a] -> [[a]]
@@ -10,26 +12,72 @@ split x (y:ys) | x == y = [] : split x ys
1012
in (y : y') : ys'
1113
split _ [] = [[]]
1214

13-
data Vec2 = Vec2 { x :: Int, y :: Int }
14-
deriving (Show, Eq, Ord)
15+
-- | Finds the period of the given function.
16+
period :: Eq a => (a -> a) -> a -> [a]
17+
period f = period' []
18+
where period' acc x | x `elem` acc = reverse acc
19+
| otherwise = period' (x : acc) (f x)
20+
21+
-- | Finds the nth element of the list (modulo the list's length) .
22+
(!!%) :: [a] -> Int -> a
23+
xs !!% n = xs !! (n `mod` length xs)
1524

16-
data Robot = Robot { pos :: Vec2, vel :: Vec2 }
25+
data Vec2 a = Vec2 { x :: a, y :: a }
26+
deriving (Show, Eq, Ord, Functor)
27+
28+
data Robot = Robot { pos :: Vec2 Int, vel :: Vec2 Int }
1729
deriving (Show, Eq, Ord)
1830

19-
parseVec2 :: String -> Vec2
31+
zipVec2With :: (a -> b -> c) -> Vec2 a -> Vec2 b -> Vec2 c
32+
zipVec2With f v w = Vec2 (f v.x w.x) (f v.y w.y)
33+
34+
(.+.) :: Num a => Vec2 a -> Vec2 a -> Vec2 a
35+
(.+.) = zipVec2With (+)
36+
37+
(.-.) :: Num a => Vec2 a -> Vec2 a -> Vec2 a
38+
(.-.) = zipVec2With (-)
39+
40+
(.%.) :: Integral a => Vec2 a -> Vec2 a -> Vec2 a
41+
(.%.) = zipVec2With mod
42+
43+
(./) :: Integral a => Vec2 a -> a -> Vec2 a
44+
v ./ x = (`div` x) <$> v
45+
46+
parseVec2 :: Read a => String -> Vec2 a
2047
parseVec2 raw = Vec2 x y
2148
where [x, y] = read <$> split ',' raw
2249

2350
parseRobot :: String -> Robot
2451
parseRobot raw = Robot pos vel
2552
where [pos, vel] = parseVec2 . drop 2 <$> split ' ' raw
2653

54+
boardSize :: Vec2 Int
55+
boardSize = Vec2 11 7
56+
57+
step :: Robot -> Robot
58+
step r = Robot ((r.pos .+. r.vel) .%. boardSize) r.vel
59+
60+
stepN :: Int -> Robot -> Robot
61+
stepN n = (!!% n) . period step
62+
63+
safetyFactor :: [Robot] -> Int
64+
safetyFactor rs = length . filter inQuadrant $ (.pos) <$> rs
65+
where center = boardSize ./ 2
66+
inQuadrant v = v.x /= center.x || v.y /= center.y
67+
68+
pretty :: [Robot] -> String
69+
pretty rs = unlines $ (\y -> join $ (\x -> showCount . length . filter (== Vec2 x y) $ (.pos) <$> rs) <$> [0..boardSize.x]) <$> [0..boardSize.y]
70+
where showCount n | n == 0 = "."
71+
| otherwise = show n
72+
2773
main :: IO ()
2874
main = do
2975
args <- getArgs
3076
case args of
3177
[path] -> do
3278
raw <- readFile' path
3379
let robots = parseRobot <$> lines raw
34-
mapM_ print robots
80+
robots1 = stepN 100 <$> robots
81+
putStrLn $ pretty robots1
82+
putStrLn $ "Part 1: " ++ show (safetyFactor robots1)
3583
_ -> putStrLn "Usage: day14 <path to input>"

0 commit comments

Comments
 (0)