Skip to content

Instantly share code, notes, and snippets.

@WitchTP
Created December 5, 2020 20:33
Show Gist options
  • Save WitchTP/99d49e90d8d844b37f0996de3a5f7b55 to your computer and use it in GitHub Desktop.
Save WitchTP/99d49e90d8d844b37f0996de3a5f7b55 to your computer and use it in GitHub Desktop.
Fifth day of Avent Code 2020
module FifthDay where
import Data.List (sort)
data FrontBack = F | B deriving (Eq, Read, Show)
data LeftRight = L | R deriving (Eq, Read, Show)
data TicketChar = Row FrontBack | Column LeftRight
data Ticket = Ticket {
row :: ![FrontBack],
column :: ![LeftRight]
}
data Seats = Seats {
seatRows :: ![Int],
seatColumns :: ![Int]
}
data Seat = Seat {
seatRow :: !Int,
seatColumn :: !Int
}
class (Eq a) => Query a where
searchHigh :: a
searchLow :: a
instance Query FrontBack where
searchHigh = F
searchLow = B
instance Query LeftRight where
searchHigh = L
searchLow = R
readTicket :: String -> Ticket
readTicket = ticketFromChars . catMaybes . fmap parseTicketChar
ticketFromChars :: [TicketChar] -> Ticket
ticketFromChars list = Ticket { row = catRows list, column = catColumns list }
catRows :: [TicketChar] -> [FrontBack]
catRows = fmap (\(Row row) -> row) . filter isRow
catColumns :: [TicketChar] -> [LeftRight]
catColumns = fmap (\(Column column) -> column) . filter isColumn
isRow :: TicketChar -> Bool
isRow (Row _) = True
isRow _ = False
isColumn :: TicketChar -> Bool
isColumn = not . isRow
isJust :: Maybe a -> Bool
isJust (Just _) = True
isJust _ = False
catMaybes :: [Maybe a] -> [a]
catMaybes = fmap (\(Just a) -> a) . filter isJust
parseTicketChar :: Char -> Maybe TicketChar
parseTicketChar 'F' = Just $ Row F
parseTicketChar 'B' = Just $ Row B
parseTicketChar 'L' = Just $ Column L
parseTicketChar 'R' = Just $ Column R
parseTicketChar _ = Nothing
partition :: [a] -> ([a], [a])
partition list = splitAt (flip div 2 $ length list + 1) list
getPosition :: (Query a) => [Int] -> [a] -> Int
getPosition (position : _) [] = position
getPosition list (char : query) = let (upperList, lowerList) = partition list in if char == searchHigh then getPosition upperList query else getPosition lowerList query
getSeatPosition :: Ticket -> Seat
getSeatPosition ticket = Seat { seatRow = getPosition (seatRows seats) (row ticket), seatColumn = getPosition (seatColumns seats) (column ticket) }
seats :: Seats
seats = Seats { seatRows = enumFromTo 0 127, seatColumns = enumFromTo 0 7 }
seatId :: Seat -> Int
seatId seat = seatRow seat * 8 + seatColumn seat
getSeatIdFromTicket :: String -> Int
getSeatIdFromTicket = seatId . getSeatPosition . readTicket
getMissingSeatId :: [Int] -> Maybe Int
getMissingSeatId [] = Nothing
getMissingSeatId (a : list) = if elem (a + 1) list then getMissingSeatId list else Just $ a + 1
result1 :: [String] -> Int
result1 = maximum . fmap getSeatIdFromTicket
result2 :: [String] -> Maybe Int
result2 = getMissingSeatId . sort . fmap getSeatIdFromTicket
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment