Day 4
This commit is contained in:
parent
1a41096917
commit
c2db929c35
|
@ -0,0 +1,72 @@
|
||||||
|
module Day4 where
|
||||||
|
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
|
||||||
|
import Data.Text (splitOn, unpack, pack)
|
||||||
|
import Prelude hiding (splitAt)
|
||||||
|
|
||||||
|
type Board = [[Int]]
|
||||||
|
|
||||||
|
column :: Board -> Int -> [Int]
|
||||||
|
column board i = map (!! i) board
|
||||||
|
|
||||||
|
splitAt :: String -> String -> [String]
|
||||||
|
splitAt delimiter str = map unpack $ splitOn (pack delimiter) $ pack str
|
||||||
|
|
||||||
|
-- remove padding spaces and turn a board line into ints
|
||||||
|
lineToInts :: String -> [Int]
|
||||||
|
lineToInts str = map read $ filter (/= "") $ splitAt " " str
|
||||||
|
|
||||||
|
isLineWinning :: [Int] -> [Int] -> Bool
|
||||||
|
isLineWinning nums = all (`elem` nums)
|
||||||
|
|
||||||
|
-- in: random numbers, board
|
||||||
|
-- out: only unmarked numbers in board
|
||||||
|
unmarkedNums :: [Int] -> Board -> Board
|
||||||
|
unmarkedNums nums = map (filter (`notElem` nums))
|
||||||
|
|
||||||
|
-- in: random numbers, board
|
||||||
|
-- out: sum of all unmarked numbers
|
||||||
|
unmarkedSum :: [Int] -> Board -> Int
|
||||||
|
unmarkedSum nums board = sum . concat $ unmarkedNums nums board
|
||||||
|
|
||||||
|
-- in: board, list of random numbers
|
||||||
|
-- out: true if board won
|
||||||
|
checkBoard :: Board -> [Int] -> Bool
|
||||||
|
checkBoard board nums = any (isLineWinning nums) allLines
|
||||||
|
where
|
||||||
|
allLines = board ++ map (column board) [0..4]
|
||||||
|
|
||||||
|
-- in: list of boards, list of random numbers
|
||||||
|
-- out: board that won, number of iterations
|
||||||
|
checkBoards' :: [Board] -> [Int] -> (Board, Int)
|
||||||
|
checkBoards' [] nums = ([], length nums)
|
||||||
|
checkBoards' (x:xs) nums
|
||||||
|
| checkBoard x nums = (x, length nums)
|
||||||
|
| otherwise = checkBoards' xs nums
|
||||||
|
|
||||||
|
-- in: list of boards, list of random numbers
|
||||||
|
-- out: board that won, number of iterations
|
||||||
|
-- will error if none of the tables are solvable
|
||||||
|
checkBoards :: [Board] -> [Int] -> Int -> (Board, Int)
|
||||||
|
checkBoards boards nums iter
|
||||||
|
| null $ fst $ checkBoards' boards list = checkBoards boards nums (iter + 1)
|
||||||
|
| otherwise = checkBoards' boards list
|
||||||
|
where
|
||||||
|
list = take iter nums
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = do
|
||||||
|
input <- openFile "inputs/4.txt" ReadMode
|
||||||
|
contents <- hGetContents input
|
||||||
|
|
||||||
|
-- random numbers from the first line
|
||||||
|
let list = map read $ splitAt "," $ head $ splitAt "\n\n" contents :: [Int]
|
||||||
|
-- the remaining lines are bingo boards
|
||||||
|
let bingus = map lines $ tail $ splitAt "\n\n" contents
|
||||||
|
let boards = map (map lineToInts) bingus
|
||||||
|
|
||||||
|
let (board, num) = checkBoards boards list 1
|
||||||
|
|
||||||
|
let sum = unmarkedSum (take num list) board
|
||||||
|
print $ sum * list !! (num - 1)
|
||||||
|
|
||||||
|
hClose input
|
|
@ -0,0 +1,72 @@
|
||||||
|
module Day4_1 where
|
||||||
|
import System.IO (openFile, IOMode (ReadMode), hClose, hGetContents)
|
||||||
|
import Data.Text (splitOn, unpack, pack)
|
||||||
|
import Prelude hiding (splitAt)
|
||||||
|
|
||||||
|
type Board = [[Int]]
|
||||||
|
|
||||||
|
column :: Board -> Int -> [Int]
|
||||||
|
column board i = map (!! i) board
|
||||||
|
|
||||||
|
splitAt :: String -> String -> [String]
|
||||||
|
splitAt delimiter str = map unpack $ splitOn (pack delimiter) $ pack str
|
||||||
|
|
||||||
|
-- remove padding spaces and turn a board line into ints
|
||||||
|
lineToInts :: String -> [Int]
|
||||||
|
lineToInts str = map read $ filter (/= "") $ splitAt " " str
|
||||||
|
|
||||||
|
isLineWinning :: [Int] -> [Int] -> Bool
|
||||||
|
isLineWinning nums = all (`elem` nums)
|
||||||
|
|
||||||
|
-- in: random numbers, board
|
||||||
|
-- out: only unmarked numbers in board
|
||||||
|
unmarkedNums :: [Int] -> Board -> Board
|
||||||
|
unmarkedNums nums = map (filter (`notElem` nums))
|
||||||
|
|
||||||
|
-- in: random numbers, board
|
||||||
|
-- out: sum of all unmarked numbers
|
||||||
|
unmarkedSum :: [Int] -> Board -> Int
|
||||||
|
unmarkedSum nums board = sum . concat $ unmarkedNums nums board
|
||||||
|
|
||||||
|
-- in: board, list of random numbers
|
||||||
|
-- out: true if board won
|
||||||
|
checkBoard :: Board -> [Int] -> Bool
|
||||||
|
checkBoard board nums = any (isLineWinning nums) allLines
|
||||||
|
where
|
||||||
|
allLines = board ++ map (column board) [0..4]
|
||||||
|
|
||||||
|
-- in: list of boards, list of random numbers
|
||||||
|
-- out: boards that won, number of iterations
|
||||||
|
checkBoards' :: [Board] -> [Int] -> [(Board, Int)] -> [(Board, Int)]
|
||||||
|
checkBoards' [] nums acc = acc
|
||||||
|
checkBoards' (x:xs) nums acc
|
||||||
|
| checkBoard x nums = checkBoards' xs nums (acc ++ [(x, length nums)])
|
||||||
|
| otherwise = checkBoards' xs nums acc
|
||||||
|
|
||||||
|
checkBoards :: [Board] -> [Int] -> [(Board, Int)]
|
||||||
|
checkBoards boards nums = filter (\x -> fst x /= []) solutions
|
||||||
|
where solutions = [ k | i <- [1..length nums],
|
||||||
|
let j = take i nums,
|
||||||
|
k <- checkBoards' boards j [] ]
|
||||||
|
|
||||||
|
dedup :: Eq a => [(a, b)] -> [(a, b)]
|
||||||
|
dedup [] = []
|
||||||
|
dedup (x:xs) = x : dedup (filter (\y -> fst x /= fst y) xs)
|
||||||
|
|
||||||
|
main :: IO ()
|
||||||
|
main = do
|
||||||
|
input <- openFile "inputs/4.txt" ReadMode
|
||||||
|
contents <- hGetContents input
|
||||||
|
|
||||||
|
-- random numbers from the first line
|
||||||
|
let list = map read $ splitAt "," $ head $ splitAt "\n\n" contents :: [Int]
|
||||||
|
-- the remaining lines are bingo boards
|
||||||
|
let bingus = map lines $ tail $ splitAt "\n\n" contents
|
||||||
|
let boards = map (map lineToInts) bingus
|
||||||
|
|
||||||
|
let (board, num) = last . dedup $ checkBoards boards list
|
||||||
|
|
||||||
|
let sum = unmarkedSum (take num list) board
|
||||||
|
print $ sum * list !! (num - 1)
|
||||||
|
|
||||||
|
hClose input
|
Loading…
Reference in New Issue