2020-12-03 13:57:18 +01:00
|
|
|
#! /usr/bin/env -S"ANSWER=42" nix-shell
|
|
|
|
#! nix-shell -p ghcid
|
|
|
|
#! nix-shell -p "haskellPackages.ghcWithPackages (p: with p; [])"
|
|
|
|
#! nix-shell -i "ghcid -c 'ghci -Wall' -T main"
|
|
|
|
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2020-12-03 16:36:12 +01:00
|
|
|
import Data.List (intersperse)
|
|
|
|
|
2020-12-03 13:57:18 +01:00
|
|
|
testData :: [String]
|
|
|
|
testData = [ "..##......."
|
|
|
|
, "#...#...#.."
|
|
|
|
, ".#....#..#."
|
|
|
|
, "..#.#...#.#"
|
|
|
|
, ".#...##..#."
|
|
|
|
, "..#.##....."
|
|
|
|
, ".#.#.#....#"
|
|
|
|
, ".#........#"
|
|
|
|
, "#.##...#..."
|
|
|
|
, "#...##....#"
|
|
|
|
, ".#..#...#.#"
|
|
|
|
]
|
|
|
|
|
2020-12-03 16:36:12 +01:00
|
|
|
data Position = Position { x_::Int, y_::Int }
|
|
|
|
|
|
|
|
instance Show (Position)
|
|
|
|
where
|
|
|
|
show p = "("<>show (x_ p)<>","<>show (y_ p)<>")"
|
|
|
|
|
|
|
|
-- Returns a half-line starting on (0,0) and following the (x*a,x*b) eq:
|
|
|
|
line :: Int -> Int -> [Position]
|
|
|
|
line a b = Position 0 0 : [ Position (x*a) (x*b) | x <- [1..] ]
|
|
|
|
|
|
|
|
-- Starting at the top-left corner of your map and following a slope of right 3
|
|
|
|
-- and down 1, how many trees would you encounter?
|
|
|
|
|
|
|
|
-- Requirements for this first task:
|
|
|
|
-- - datastructure supporting random-access (or similar) interface (lists would work)
|
|
|
|
-- - function generating a list of (x,y) coordinate to check
|
|
|
|
-- - must have 2D datastructure, since it's infinite on 1D (x axis)
|
|
|
|
-- - in this version at least, there's no need to modify the datastructure, so
|
|
|
|
-- it can be read-only, or even just a function taking a position and returning
|
|
|
|
-- SquareSortEmpty or SquareSortTree
|
|
|
|
|
|
|
|
data SquareSort = SquareSortTree | SquareSortEmpty
|
2020-12-03 21:11:19 +01:00
|
|
|
deriving Eq
|
2020-12-03 16:36:12 +01:00
|
|
|
|
|
|
|
instance Show SquareSort
|
|
|
|
where
|
|
|
|
show SquareSortTree = "#"
|
2020-12-03 21:11:19 +01:00
|
|
|
show SquareSortEmpty = "_"
|
2020-12-03 16:36:12 +01:00
|
|
|
|
|
|
|
char2ss :: Char -> Maybe SquareSort
|
|
|
|
char2ss '#' = Just SquareSortTree
|
|
|
|
char2ss '.' = Just SquareSortEmpty
|
|
|
|
char2ss _ = Nothing
|
|
|
|
|
|
|
|
str2sss :: String -> Maybe [SquareSort]
|
|
|
|
str2sss = sequence . (map char2ss)
|
|
|
|
|
|
|
|
newtype Grid = Grid [[SquareSort]]
|
|
|
|
|
|
|
|
instance Show (Grid)
|
|
|
|
where
|
2020-12-03 21:11:19 +01:00
|
|
|
show (Grid x) = concat $ intersperse "\n" $ map show x
|
2020-12-03 16:36:12 +01:00
|
|
|
|
|
|
|
parseInput :: [String] -> Maybe Grid
|
|
|
|
parseInput x = Grid <$> sequence ( (map str2sss) x )
|
|
|
|
|
|
|
|
getSquareSortAtPosition :: Grid -> Position -> SquareSort
|
|
|
|
getSquareSortAtPosition (Grid grid) (Position x y) =
|
|
|
|
grid !! y !! (x `mod` n)
|
|
|
|
where
|
|
|
|
n = length (grid !! 0)
|
|
|
|
|
2020-12-03 21:11:19 +01:00
|
|
|
solveDay3Part1 :: Grid -> (Int,Int) -> Int
|
|
|
|
solveDay3Part1 grid@(Grid lx) (x',y')=
|
|
|
|
length $ filter (== SquareSortTree) $ map (getSquareSortAtPosition grid) px
|
|
|
|
where
|
2020-12-03 21:23:26 +01:00
|
|
|
px = take n' $ line x' y'
|
|
|
|
n' = if y' > 1 then n + 1 else n
|
2020-12-03 21:11:19 +01:00
|
|
|
n = (length lx) `div` y'
|
|
|
|
|
|
|
|
-- Determine the number of trees you would encounter if, for each of the
|
|
|
|
-- following slopes, you start at the top-left corner and traverse the map all
|
|
|
|
-- the way to the bottom:
|
|
|
|
--
|
|
|
|
-- - Right 1, down 1.
|
|
|
|
-- - Right 3, down 1. (This is the slope you already checked.)
|
|
|
|
-- - Right 5, down 1.
|
|
|
|
-- - Right 7, down 1.
|
|
|
|
-- - Right 1, down 2.
|
|
|
|
--
|
|
|
|
-- What do you get if you multiply together the number of trees encountered on
|
|
|
|
-- each of the listed slopes?
|
|
|
|
|
|
|
|
solveDay3Part2 :: Grid -> Int
|
|
|
|
solveDay3Part2 grid =
|
|
|
|
foldl (*) 1 [ solveDay3Part1 grid (1,1)
|
|
|
|
, solveDay3Part1 grid (3,1)
|
|
|
|
, solveDay3Part1 grid (5,1)
|
|
|
|
, solveDay3Part1 grid (7,1)
|
|
|
|
, solveDay3Part1 grid (1,2)
|
|
|
|
]
|
|
|
|
|
2020-12-03 13:57:18 +01:00
|
|
|
main :: IO ()
|
|
|
|
main = do
|
|
|
|
putStrLn "Day 3 - Part 1"
|
2020-12-03 21:11:19 +01:00
|
|
|
inputData <- readFile "day3/input"
|
2020-12-03 16:36:12 +01:00
|
|
|
print $ take 5 $ line 3 1
|
2020-12-03 21:23:26 +01:00
|
|
|
print $ take 6 $ line 1 2
|
2020-12-03 16:36:12 +01:00
|
|
|
let (Just parsedTestData) = parseInput testData
|
|
|
|
print parsedTestData
|
2020-12-03 21:23:26 +01:00
|
|
|
print $ getSquareSortAtPosition parsedTestData (Position 5 10)
|
2020-12-03 21:11:19 +01:00
|
|
|
let (Just parsedInputData) = parseInput (lines inputData)
|
|
|
|
putStrLn "Part 1:"
|
|
|
|
print $ solveDay3Part1 parsedTestData (3,1)
|
|
|
|
print $ solveDay3Part1 parsedInputData (3,1)
|
|
|
|
putStrLn "Part 2:"
|
2020-12-03 21:23:26 +01:00
|
|
|
print $ solveDay3Part2 parsedTestData
|
|
|
|
print $ solveDay3Part2 parsedInputData
|