aboutsummaryrefslogtreecommitdiff
path: root/2020/16a.hs
diff options
context:
space:
mode:
authorAria <me@aria.rip>2023-01-02 21:58:56 +0000
committerAria <me@aria.rip>2023-01-02 21:58:56 +0000
commit5eb58ad076f2cd435b11b140820da224b60b73d5 (patch)
tree2a67939595fbf993ff04f69b9cd3f0aa20827d96 /2020/16a.hs
initial commit
Diffstat (limited to '2020/16a.hs')
-rw-r--r--2020/16a.hs69
1 files changed, 69 insertions, 0 deletions
diff --git a/2020/16a.hs b/2020/16a.hs
new file mode 100644
index 0000000..0342e5d
--- /dev/null
+++ b/2020/16a.hs
@@ -0,0 +1,69 @@
+module Day16A where
+
+import System.Environment (getArgs)
+import Text.Printf
+import Data.List.Split (splitOn)
+
+
+-- name, (lo, hi)
+type FieldDef = (String, [(Int, Int)])
+
+-- (fields, your ticket, nearby tickets)
+type Input = ([FieldDef], [Int], [[Int]])
+
+parseTicketLine :: String -> [Int]
+parseTicketLine = map read . splitOn ","
+
+parseRange :: String -> (Int, Int)
+parseRange x = (head ns, last ns)
+ where ns = map read $ splitOn "-" x
+
+parseFieldDef :: String -> FieldDef
+parseFieldDef x = (n, ranges)
+ where [n, rs] = splitOn ": " x
+ ranges = map parseRange $ splitOn " or " rs
+
+parseFields :: [String] -> [FieldDef]
+parseFields = inner . head . splitOn [""]
+ where inner = map parseFieldDef
+
+
+findYourTicket :: [String] -> [Int]
+findYourTicket ("your ticket:":xs) = parseTicketLine (head xs)
+findYourTicket (_:xs) = findYourTicket xs
+findYourTicket [] = error "Couldn't find your ticket"
+
+findOtherTickets :: [String] -> [[Int]]
+findOtherTickets ("nearby tickets:":xs) = map parseTicketLine xs
+findOtherTickets (_:xs) = findOtherTickets xs
+findOtherTickets [] = error "Couldn't find nearby tickets"
+
+
+-- Parse the input
+parseInput :: String -> Input
+parseInput xs = (parseFields ls, findYourTicket ls, findOtherTickets ls)
+ where ls = lines xs
+
+-- Parse a file given the path
+-- Returns list of instructions
+parseFromFile :: String -> IO Input
+parseFromFile s = do
+ contents <- readFile s;
+ return $ parseInput contents;
+
+fieldValid :: FieldDef -> Int -> Bool
+fieldValid (_, rs) x = any (\(l,h) -> x >= l && x <= h) rs
+
+invalidValues :: Input -> [Int]
+invalidValues (cs, _, ts) = concat [filter (\x -> not (any (`fieldValid` x) cs)) t | t <- ts]
+
+-- runghc --ghc-arg='-package split' 16a.hs inputs/day16
+main :: IO ()
+main = do
+ args <- getArgs;
+ i <- parseFromFile (head args);
+ let vs = invalidValues i;
+
+ printf "Answer = %d\n" (sum vs) :: IO ();
+
+ return ();