{-# LANGUAGE OverloadedStrings #-} -- for building Text strings module Main where import Control.Applicative (Alternative((<|>))) import Control.Monad (replicateM) import Data.Text.Lazy (Text) import Data.Void (Void) import Prelude import qualified Data.List as List import qualified Data.Text.Lazy.Encoding as Text import qualified Text.Megaparsec as P import qualified Text.Megaparsec.Char as P -- import qualified Text.Megaparsec.Debug as P import qualified Data.ByteString.Lazy as BSL import Paths_AoC2020 -- | See https://adventofcode.com/2020/day/5 for the problem statements data Day05Results = Day05Results { example1 :: SeatID , batch1 :: SeatID , batch2 :: SeatID } deriving (Show) type SeatID = Int main :: IO () main = do putStr "Day05Inputs: " >> getDataFileName "" >>= putStrLn print =<< Day05Results <$> parseMaxSeatID "example" <*> parseMaxSeatID "batch" <*> parseMySeatID "batch" parserSeatID :: Parser SeatID parserSeatID = -- P.dbg "parserSeatID" $ (\rows cols -> mkBinary rows * 8 + mkBinary cols) <$> replicateM 7 parserRow <*> replicateM 3 parserColumns where mkBinary :: [Bool] -> Int mkBinary = List.foldl' (\acc bit -> acc * 2 + if bit then 1 else 0) 0 parserRow :: Parser Bool parserRow = False <$ P.char 'F' <|> True <$ P.char 'B' parserColumns :: Parser Bool parserColumns = False <$ P.char 'L' <|> True <$ P.char 'R' type Parser output = P.Parsec {-error-}Void {-input-}Text output parseSeatIDs :: FilePath -> IO [SeatID] parseSeatIDs input = do content <- Text.decodeUtf8 <$> (BSL.readFile =<< getDataFileName input) case P.parse (P.many (parserSeatID <* P.char '\n') <* P.eof) input content of Left err -> error (P.errorBundlePretty err) Right seatIDs -> return seatIDs parseMaxSeatID :: FilePath -> IO SeatID parseMaxSeatID = (maximum <$>) . parseSeatIDs parseMySeatID :: FilePath -> IO SeatID parseMySeatID input = do seatIDs <- parseSeatIDs input return $ go $ List.sort seatIDs where go (s0:s1:ss) | s0 + 1 == s1 = go (s1:ss) | otherwise = s0 + 1 go _ = error "no empty seat"