Refactored day 4 solution

This commit is contained in:
Riley Apeldoorn 2021-12-04 12:52:39 +01:00
parent 2cdc0878a2
commit db59bb39be
1 changed files with 40 additions and 52 deletions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE TupleSections #-}
import Data.List import Data.List
import Debug.Trace import Debug.Trace
@ -8,67 +9,54 @@ type Input = ([Int], [Board])
parse :: [String] -> Input parse :: [String] -> Input
parse (l : ls) = (n, b) parse (l : ls) = (n, b)
where where n = map read $ words [ if c == ',' then ' ' else c | c <- l ]
n = map read (words [ if c == ',' then ' ' else c | c <- l ]) b = parseBoards (filter (/= "") ls)
b = parseBoards (filter (/= "") ls)
solve :: Input -> (Int, Int)
solve input = (f input, g input)
where f = uncurry winBingo
g = uncurry loseBingo
parseBoards :: [String] -> [Board] parseBoards :: [String] -> [Board]
parseBoards [] = [] parseBoards [] = []
parseBoards list = Board (map (map (Unmarked . read) . words) a) : parseBoards b parseBoards l = parse a : parseBoards b
where where (a,b) = splitAt 5 l
(a, b) = splitAt 5 list parse = map $ map (Unmarked . read) . words
newtype Board = Board [[Cell]] type Board = [[Cell]]
deriving
Show rows :: Board -> [[Cell]]
rows = id
cols :: Board -> [[Cell]]
cols = transpose
hasWon :: Board -> Bool
hasWon b = check (rows b) || check (cols b)
where check = any $ all marked
score :: Int -> Board -> Int
score n b = n * sum [ x | c <- b, Unmarked x <- c ]
call :: Int -> Board -> Board
call n = map (map mark)
where mark (Unmarked x) | x == n = Marked x
mark x = x
data Cell = Unmarked Int data Cell = Unmarked Int
| Marked Int | Marked Int
deriving
Show
hasWon :: Board -> Bool marked :: Cell -> Bool
hasWon (Board b) = completed b || completed (transpose b) marked (Marked _) = True
where marked _ = False
completed = any (all isMarked)
isMarked :: Cell -> Bool solve :: Input -> (Int, Int)
isMarked (Marked _) = True solve input = (f input, g input)
isMarked _ = False where wins extr (n,b) = uncurry score $ extr $ bingo n b
f = wins head
g = wins last
winBingo :: [Int] -> [Board] -> Int bingo :: [Int] -> [Board] -> [(Int, Board)]
winBingo (n : ns) (b : bs) = bingo _ [] = []
if any hasWon r bingo (n : ns) (b : bs) = map (n,) w ++ bingo ns l
then score n $ head (filter hasWon r) where (w,l) = partition hasWon r
else winBingo ns r r = iter n (b : bs)
where
r = iter n (b : bs)
loseBingo :: [Int] -> [Board] -> Int
loseBingo (n : ns) [board]
| hasWon b = score n b
| otherwise = loseBingo ns [b]
where
[b] = iter n [board]
loseBingo (n : ns) (b : bs) =
loseBingo ns (filter (not . hasWon) r)
where
r = iter n (b : bs)
iter :: Int -> [Board] -> [Board] iter :: Int -> [Board] -> [Board]
iter n (b : bs) = callNumber n b : iter n bs
iter _ [] = [] iter _ [] = []
iter n (b : bs) = call n b : iter n bs
callNumber :: Int -> Board -> Board
callNumber n (Board b) = Board (map (map mark) b)
where
mark (Unmarked x) | x == n = Marked x
mark v = v
score :: Int -> Board -> Int
score n (Board b) = n * sum [ x | c <- b, Unmarked x <- c ]