#! /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 #-} import Data.List (intersperse) testData :: [String] testData = [ "..##......." , "#...#...#.." , ".#....#..#." , "..#.#...#.#" , ".#...##..#." , "..#.##....." , ".#.#.#....#" , ".#........#" , "#.##...#..." , "#...##....#" , ".#..#...#.#" ] 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 instance Show SquareSort where show SquareSortTree = "#" show SquareSortEmpty = "." 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 show (Grid x) = intersperse '\n' $ map show x 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) main :: IO () main = do putStrLn "Day 3 - Part 1" print $ take 5 $ line 3 1 let (Just parsedTestData) = parseInput testData print parsedTestData print $ getSquareSortAtPosition parsedTestData (Position 3 0)